{-# 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.Public.Feature where

import Galley.API.Teams
import Galley.API.Teams.Features
import Galley.API.Teams.Features.Get
import Galley.App
import Imports
import Wire.API.Routes.API
import Wire.API.Routes.Public.Galley.Feature
import Wire.API.Team.Feature

featureAPIGetPut :: forall cfg r. (_) => API (FeatureAPIGetPut cfg) r
featureAPIGetPut :: API (FeatureAPIGetPut cfg) r
featureAPIGetPut =
  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", cfg) ServerT
  (Description (FeatureAPIDesc cfg)
   :> (ZUser
       :> (Summary (AppendSymbol "Get config for " (FeatureSymbol cfg))
           :> (CanThrow OperationDenied
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow 'TeamNotFound
                       :> ("teams"
                           :> (Capture "tid" TeamId
                               :> ("features"
                                   :> (FeatureSymbol cfg
                                       :> Get '[JSON] (LockableFeature cfg)))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Description (FeatureAPIDesc cfg)
            :> (ZUser
                :> (Summary (AppendSymbol "Get config for " (FeatureSymbol cfg))
                    :> (CanThrow OperationDenied
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> (FeatureSymbol cfg
                                                :> Get '[JSON] (LockableFeature cfg))))))))))))
        r))
UserId
-> TeamId
-> Sem
     (Error (Tagged OperationDenied ())
        : Error (Tagged 'NotATeamMember ())
        : Error (Tagged 'TeamNotFound ()) : r)
     (LockableFeature cfg)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member TeamFeatureStore r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member TeamStore r) =>
UserId -> TeamId -> Sem r (LockableFeature cfg)
getFeature
    API
  (Named
     '("get", cfg)
     (Description (FeatureAPIDesc cfg)
      :> (ZUser
          :> (Summary (AppendSymbol "Get config for " (FeatureSymbol cfg))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol cfg
                                          :> Get '[JSON] (LockableFeature cfg))))))))))))
  r
-> API
     (Named
        '("put", cfg)
        (Description (FeatureAPIDesc cfg)
         :> (ZUser
             :> (Summary (AppendSymbol "Put config for " (FeatureSymbol cfg))
                 :> (CanThrow OperationDenied
                     :> (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 (FeatureAPIGetPut 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 @'("put", cfg) ServerT
  (Description (FeatureAPIDesc cfg)
   :> (ZUser
       :> (Summary (AppendSymbol "Put config for " (FeatureSymbol cfg))
           :> (CanThrow OperationDenied
               :> (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)
            :> (ZUser
                :> (Summary (AppendSymbol "Put config for " (FeatureSymbol cfg))
                    :> (CanThrow OperationDenied
                        :> (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))
UserId
-> TeamId
-> Feature cfg
-> Sem
     (Error (Tagged OperationDenied ())
        : 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 'NotATeamMember ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member (Error TeamFeatureError) r, Member (Input Opts) r,
 Member TeamStore r, Member TeamFeatureStore r,
 Member (Logger (Msg -> Msg)) r, Member NotificationSubsystem r) =>
UserId -> TeamId -> Feature cfg -> Sem r (LockableFeature cfg)
setFeature

featureAPI :: API FeatureAPI GalleyEffects
featureAPI :: API FeatureAPI GalleyEffects
featureAPI =
  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", SSOConfig) ServerT
  (Description ""
   :> (ZUser
       :> (Summary "Get config for sso"
           :> (CanThrow OperationDenied
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow 'TeamNotFound
                       :> ("teams"
                           :> (Capture "tid" TeamId
                               :> ("features"
                                   :> ("sso" :> Get '[JSON] (LockableFeature SSOConfig)))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Description ""
            :> (ZUser
                :> (Summary "Get config for sso"
                    :> (CanThrow OperationDenied
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("sso"
                                                :> Get
                                                     '[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]))
UserId
-> TeamId
-> Sem
     '[Error (Tagged OperationDenied ()),
       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]
     (LockableFeature SSOConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member TeamFeatureStore r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member TeamStore r) =>
UserId -> TeamId -> Sem r (LockableFeature cfg)
getFeature
    API
  (Named
     '("get", SSOConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for sso"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("sso"
                                          :> Get '[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
         '("get", LegalholdConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for legalhold"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("legalhold"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature LegalholdConfig)))))))))))
       :<|> Named
              '("put", LegalholdConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for legalhold"
                       :> (CanThrow OperationDenied
                           :> (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
               '("get", SearchVisibilityAvailableConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for searchVisibility"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("searchVisibility"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            SearchVisibilityAvailableConfig)))))))))))
             :<|> Named
                    '("put", SearchVisibilityAvailableConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for searchVisibility"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("searchVisibility"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          SearchVisibilityAvailableConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             SearchVisibilityAvailableConfig)))))))))))))))
            :<|> (Named
                    "get-search-visibility"
                    (Summary "Shows the value for search visibility"
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (ZLocalUser
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("search-visibility"
                                             :> Get '[JSON] TeamSearchVisibilityView)))))))
                  :<|> (Named
                          "set-search-visibility"
                          (Summary "Sets the search visibility for the whole team"
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamSearchVisibilityNotEnabled
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (ZLocalUser
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("search-visibility"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     TeamSearchVisibilityView
                                                                   :> MultiVerb
                                                                        'PUT
                                                                        '[JSON]
                                                                        '[RespondEmpty
                                                                            204
                                                                            "Search visibility set"]
                                                                        ())))))))))))
                        :<|> (Named
                                '("get", ValidateSAMLEmailsConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Get config for validateSAMLemails"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("validateSAMLemails"
                                                                     :> Get
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             ValidateSAMLEmailsConfig)))))))))))
                              :<|> (Named
                                      '("get", DigitalSignaturesConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Get config for digitalSignatures"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("digitalSignatures"
                                                                           :> Get
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   DigitalSignaturesConfig)))))))))))
                                    :<|> ((Named
                                             '("get", AppLockConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary "Get config for appLock"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("appLock"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          AppLockConfig)))))))))))
                                           :<|> Named
                                                  '("put", AppLockConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary "Put config for appLock"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("appLock"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        AppLockConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           AppLockConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", FileSharingConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary "Get config for fileSharing"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("fileSharing"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                FileSharingConfig)))))))))))
                                                 :<|> Named
                                                        '("put", FileSharingConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for fileSharing"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("fileSharing"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              FileSharingConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 FileSharingConfig)))))))))))))))
                                                :<|> (Named
                                                        '("get", ClassifiedDomainsConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Get config for classifiedDomains"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("classifiedDomains"
                                                                                             :> Get
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     ClassifiedDomainsConfig)))))))))))
                                                      :<|> ((Named
                                                               '("get", ConferenceCallingConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for conferenceCalling"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("conferenceCalling"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            ConferenceCallingConfig)))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      ConferenceCallingConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for conferenceCalling"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("conferenceCalling"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          ConferenceCallingConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             ConferenceCallingConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get",
                                                                       SelfDeletingMessagesConfig)
                                                                     (Description ""
                                                                      :> (ZUser
                                                                          :> (Summary
                                                                                "Get config for selfDeletingMessages"
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("selfDeletingMessages"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  SelfDeletingMessagesConfig)))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            SelfDeletingMessagesConfig)
                                                                          (Description ""
                                                                           :> (ZUser
                                                                               :> (Summary
                                                                                     "Put config for selfDeletingMessages"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("selfDeletingMessages"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                SelfDeletingMessagesConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   SelfDeletingMessagesConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             GuestLinksConfig)
                                                                           (Description ""
                                                                            :> (ZUser
                                                                                :> (Summary
                                                                                      "Get config for conversationGuestLinks"
                                                                                    :> (CanThrow
                                                                                          OperationDenied
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("conversationGuestLinks"
                                                                                                                :> Get
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        GuestLinksConfig)))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  GuestLinksConfig)
                                                                                (Description ""
                                                                                 :> (ZUser
                                                                                     :> (Summary
                                                                                           "Put config for conversationGuestLinks"
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (Feature
                                                                                                                                      GuestLinksConfig)
                                                                                                                                 :> Put
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         GuestLinksConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get",
                                                                                   SndFactorPasswordChallengeConfig)
                                                                                 (Description ""
                                                                                  :> (ZUser
                                                                                      :> (Summary
                                                                                            "Get config for sndFactorPasswordChallenge"
                                                                                          :> (CanThrow
                                                                                                OperationDenied
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("sndFactorPasswordChallenge"
                                                                                                                      :> Get
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              SndFactorPasswordChallengeConfig)))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        SndFactorPasswordChallengeConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (ZUser
                                                                                           :> (Summary
                                                                                                 "Put config for sndFactorPasswordChallenge"
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 TeamFeatureError
                                                                                                               :> (CanThrowMany
                                                                                                                     '[]
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         (Feature
                                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                                       :> Put
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               SndFactorPasswordChallengeConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("get",
                                                                                         MLSConfig)
                                                                                       (From 'V5
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (ZUser
                                                                                                :> (Summary
                                                                                                      "Get config for mls"
                                                                                                    :> (CanThrow
                                                                                                          OperationDenied
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mls"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        MLSConfig))))))))))))
                                                                                     :<|> Named
                                                                                            '("put",
                                                                                              MLSConfig)
                                                                                            (From
                                                                                               'V5
                                                                                             :> (Description
                                                                                                   ""
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Put config for mls"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("mls"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (Feature
                                                                                                                                                      MLSConfig)
                                                                                                                                                 :> Put
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MLSConfig))))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("get",
                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (ZUser
                                                                                                  :> (Summary
                                                                                                        "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                      :> (CanThrow
                                                                                                            OperationDenied
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                  :> Get
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                                                           :<|> Named
                                                                                                  '("put",
                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (ZUser
                                                                                                       :> (Summary
                                                                                                             "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             TeamFeatureError
                                                                                                                           :> (CanThrowMany
                                                                                                                                 '[]
                                                                                                                               :> ("teams"
                                                                                                                                   :> (Capture
                                                                                                                                         "tid"
                                                                                                                                         TeamId
                                                                                                                                       :> ("features"
                                                                                                                                           :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     (Feature
                                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                   :> Put
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("get",
                                                                                                     SearchVisibilityInboundConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (ZUser
                                                                                                        :> (Summary
                                                                                                              "Get config for searchVisibilityInbound"
                                                                                                            :> (CanThrow
                                                                                                                  OperationDenied
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("searchVisibilityInbound"
                                                                                                                                        :> Get
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeature
                                                                                                                                                SearchVisibilityInboundConfig)))))))))))
                                                                                                 :<|> Named
                                                                                                        '("put",
                                                                                                          SearchVisibilityInboundConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (ZUser
                                                                                                             :> (Summary
                                                                                                                   "Put config for searchVisibilityInbound"
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   TeamFeatureError
                                                                                                                                 :> (CanThrowMany
                                                                                                                                       '[]
                                                                                                                                     :> ("teams"
                                                                                                                                         :> (Capture
                                                                                                                                               "tid"
                                                                                                                                               TeamId
                                                                                                                                             :> ("features"
                                                                                                                                                 :> ("searchVisibilityInbound"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           (Feature
                                                                                                                                                              SearchVisibilityInboundConfig)
                                                                                                                                                         :> Put
                                                                                                                                                              '[JSON]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 SearchVisibilityInboundConfig)))))))))))))))
                                                                                                :<|> ((Named
                                                                                                         '("get",
                                                                                                           OutlookCalIntegrationConfig)
                                                                                                         (Description
                                                                                                            ""
                                                                                                          :> (ZUser
                                                                                                              :> (Summary
                                                                                                                    "Get config for outlookCalIntegration"
                                                                                                                  :> (CanThrow
                                                                                                                        OperationDenied
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                'TeamNotFound
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("outlookCalIntegration"
                                                                                                                                              :> Get
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeature
                                                                                                                                                      OutlookCalIntegrationConfig)))))))))))
                                                                                                       :<|> Named
                                                                                                              '("put",
                                                                                                                OutlookCalIntegrationConfig)
                                                                                                              (Description
                                                                                                                 ""
                                                                                                               :> (ZUser
                                                                                                                   :> (Summary
                                                                                                                         "Put config for outlookCalIntegration"
                                                                                                                       :> (CanThrow
                                                                                                                             OperationDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'TeamNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         TeamFeatureError
                                                                                                                                       :> (CanThrowMany
                                                                                                                                             '[]
                                                                                                                                           :> ("teams"
                                                                                                                                               :> (Capture
                                                                                                                                                     "tid"
                                                                                                                                                     TeamId
                                                                                                                                                   :> ("features"
                                                                                                                                                       :> ("outlookCalIntegration"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (Feature
                                                                                                                                                                    OutlookCalIntegrationConfig)
                                                                                                                                                               :> Put
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (LockableFeature
                                                                                                                                                                       OutlookCalIntegrationConfig)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get",
                                                                                                                MlsE2EIdConfig)
                                                                                                              (From
                                                                                                                 'V5
                                                                                                               :> (Description
                                                                                                                     ""
                                                                                                                   :> (ZUser
                                                                                                                       :> (Summary
                                                                                                                             "Get config for mlsE2EId"
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("mlsE2EId"
                                                                                                                                                       :> Get
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               MlsE2EIdConfig))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "put-MlsE2EIdConfig@v5"
                                                                                                                    (From
                                                                                                                       'V5
                                                                                                                     :> (Until
                                                                                                                           'V6
                                                                                                                         :> (ZUser
                                                                                                                             :> (Summary
                                                                                                                                   "Put config for mlsE2EId"
                                                                                                                                 :> (CanThrow
                                                                                                                                       OperationDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("mlsE2EId"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (Feature
                                                                                                                                                                              MlsE2EIdConfig)
                                                                                                                                                                         :> Put
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 MlsE2EIdConfig)))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("put",
                                                                                                                            MlsE2EIdConfig)
                                                                                                                          (From
                                                                                                                             'V6
                                                                                                                           :> (Description
                                                                                                                                 ""
                                                                                                                               :> (ZUser
                                                                                                                                   :> (Summary
                                                                                                                                         "Put config for mlsE2EId"
                                                                                                                                       :> (CanThrow
                                                                                                                                             OperationDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("mlsE2EId"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (Feature
                                                                                                                                                                                    MlsE2EIdConfig)
                                                                                                                                                                               :> Put
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       MlsE2EIdConfig)))))))))))))))
                                                                                                                        :<|> ((Named
                                                                                                                                 '("get",
                                                                                                                                   MlsMigrationConfig)
                                                                                                                                 (From
                                                                                                                                    'V5
                                                                                                                                  :> (Description
                                                                                                                                        ""
                                                                                                                                      :> (ZUser
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for mlsMigration"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    OperationDenied
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("mlsMigration"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MlsMigrationConfig))))))))))))
                                                                                                                               :<|> Named
                                                                                                                                      '("put",
                                                                                                                                        MlsMigrationConfig)
                                                                                                                                      (From
                                                                                                                                         'V5
                                                                                                                                       :> (Description
                                                                                                                                             ""
                                                                                                                                           :> (ZUser
                                                                                                                                               :> (Summary
                                                                                                                                                     "Put config for mlsMigration"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         OperationDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("mlsMigration"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (Feature
                                                                                                                                                                                                MlsMigrationConfig)
                                                                                                                                                                                           :> Put
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   MlsMigrationConfig))))))))))))))))
                                                                                                                              :<|> ((Named
                                                                                                                                       '("get",
                                                                                                                                         EnforceFileDownloadLocationConfig)
                                                                                                                                       (From
                                                                                                                                          'V5
                                                                                                                                        :> (Description
                                                                                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                            :> (ZUser
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for enforceFileDownloadLocation"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          OperationDenied
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        EnforceFileDownloadLocationConfig))))))))))))
                                                                                                                                     :<|> Named
                                                                                                                                            '("put",
                                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                                            (From
                                                                                                                                               'V5
                                                                                                                                             :> (Description
                                                                                                                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                 :> (ZUser
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Put config for enforceFileDownloadLocation"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               OperationDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("enforceFileDownloadLocation"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (Feature
                                                                                                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                 :> Put
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get",
                                                                                                                                              LimitedEventFanoutConfig)
                                                                                                                                            (From
                                                                                                                                               'V5
                                                                                                                                             :> (Description
                                                                                                                                                   ""
                                                                                                                                                 :> (ZUser
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Get config for limitedEventFanout"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               OperationDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("teams"
                                                                                                                                                                         :> (Capture
                                                                                                                                                                               "tid"
                                                                                                                                                                               TeamId
                                                                                                                                                                             :> ("features"
                                                                                                                                                                                 :> ("limitedEventFanout"
                                                                                                                                                                                     :> Get
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             LimitedEventFanoutConfig))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-all-feature-configs-for-user"
                                                                                                                                                  (Summary
                                                                                                                                                     "Gets feature configs for a user"
                                                                                                                                                   :> (Description
                                                                                                                                                         "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                             'ReadFeatureConfigs
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> Get
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    AllTeamFeatures))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-all-feature-configs-for-team"
                                                                                                                                                        (Summary
                                                                                                                                                           "Gets feature configs for a team"
                                                                                                                                                         :> (Description
                                                                                                                                                               "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       OperationDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              AllTeamFeatures)))))))))
                                                                                                                                                      :<|> ((Named
                                                                                                                                                               '("get-deprecated",
                                                                                                                                                                 SearchVisibilityAvailableConfig)
                                                                                                                                                               (ZUser
                                                                                                                                                                :> (Summary
                                                                                                                                                                      "[deprecated] Get config for searchVisibility"
                                                                                                                                                                    :> (Until
                                                                                                                                                                          'V2
                                                                                                                                                                        :> (Description
                                                                                                                                                                              "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> ("teams"
                                                                                                                                                                                            :> (Capture
                                                                                                                                                                                                  "tid"
                                                                                                                                                                                                  TeamId
                                                                                                                                                                                                :> ("features"
                                                                                                                                                                                                    :> ("search-visibility"
                                                                                                                                                                                                        :> Get
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                SearchVisibilityAvailableConfig))))))))))))
                                                                                                                                                             :<|> (Named
                                                                                                                                                                     '("put-deprecated",
                                                                                                                                                                       SearchVisibilityAvailableConfig)
                                                                                                                                                                     (ZUser
                                                                                                                                                                      :> (Summary
                                                                                                                                                                            "[deprecated] Get config for searchVisibility"
                                                                                                                                                                          :> (Until
                                                                                                                                                                                'V2
                                                                                                                                                                              :> (Description
                                                                                                                                                                                    "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    TeamFeatureError
                                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                                            "tid"
                                                                                                                                                                                                            TeamId
                                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                                              :> ("search-visibility"
                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (Feature
                                                                                                                                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                                                                                                                                      :> Put
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                                                              SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                                                                   :<|> (Named
                                                                                                                                                                           '("get-deprecated",
                                                                                                                                                                             ValidateSAMLEmailsConfig)
                                                                                                                                                                           (ZUser
                                                                                                                                                                            :> (Summary
                                                                                                                                                                                  "[deprecated] Get config for validateSAMLemails"
                                                                                                                                                                                :> (Until
                                                                                                                                                                                      'V2
                                                                                                                                                                                    :> (Description
                                                                                                                                                                                          "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                                              "tid"
                                                                                                                                                                                                              TeamId
                                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                                :> ("validate-saml-emails"
                                                                                                                                                                                                                    :> Get
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                                                            ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                                                         :<|> Named
                                                                                                                                                                                '("get-deprecated",
                                                                                                                                                                                  DigitalSignaturesConfig)
                                                                                                                                                                                (ZUser
                                                                                                                                                                                 :> (Summary
                                                                                                                                                                                       "[deprecated] Get config for digitalSignatures"
                                                                                                                                                                                     :> (Until
                                                                                                                                                                                           'V2
                                                                                                                                                                                         :> (Description
                                                                                                                                                                                               "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                                     :> ("digital-signatures"
                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                 DigitalSignaturesConfig)))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      LegalholdConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature legalhold"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("legalhold"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             LegalholdConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            SSOConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature sso"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("sso"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   SSOConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  SearchVisibilityAvailableConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("searchVisibility"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         SearchVisibilityAvailableConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        ValidateSAMLEmailsConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("validateSAMLemails"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              DigitalSignaturesConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("digitalSignatures"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     DigitalSignaturesConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    AppLockConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature appLock"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("appLock"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           AppLockConfig))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        '("get-config",
                                                                                                                                                                                                          FileSharingConfig)
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                                                                     :> ("fileSharing"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                 FileSharingConfig))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              '("get-config",
                                                                                                                                                                                                                ClassifiedDomainsConfig)
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                                                                           :> ("classifiedDomains"
                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                                       ClassifiedDomainsConfig))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    '("get-config",
                                                                                                                                                                                                                      ConferenceCallingConfig)
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                                                                 :> ("conferenceCalling"
                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                                             ConferenceCallingConfig))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          '("get-config",
                                                                                                                                                                                                                            SelfDeletingMessagesConfig)
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                                                                       :> ("selfDeletingMessages"
                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                                                                   SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                '("get-config",
                                                                                                                                                                                                                                  GuestLinksConfig)
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                                                                         GuestLinksConfig))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                                                                               SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                                                                           '("get-config",
                                                                                                                                                                                                                                             MLSConfig)
                                                                                                                                                                                                                                           (Summary
                                                                                                                                                                                                                                              "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                                                            :> (Until
                                                                                                                                                                                                                                                  'V2
                                                                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                                                                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                                    :> (ZUser
                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                                                                    :> ("feature-configs"
                                                                                                                                                                                                                                                                        :> ("mls"
                                                                                                                                                                                                                                                                            :> Get
                                                                                                                                                                                                                                                                                 '[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
        '("get", SSOConfig)
        (Description ""
         :> (ZUser
             :> (Summary "Get config for sso"
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> ("sso"
                                             :> Get '[JSON] (LockableFeature SSOConfig)))))))))))
      :<|> ((Named
               '("get", LegalholdConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for legalhold"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("legalhold"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature LegalholdConfig)))))))))))
             :<|> Named
                    '("put", LegalholdConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for legalhold"
                             :> (CanThrow OperationDenied
                                 :> (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
                     '("get", SearchVisibilityAvailableConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for searchVisibility"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("searchVisibility"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  SearchVisibilityAvailableConfig)))))))))))
                   :<|> Named
                          '("put", SearchVisibilityAvailableConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for searchVisibility"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("searchVisibility"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                SearchVisibilityAvailableConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   SearchVisibilityAvailableConfig)))))))))))))))
                  :<|> (Named
                          "get-search-visibility"
                          (Summary "Shows the value for search visibility"
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (ZLocalUser
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("search-visibility"
                                                   :> Get '[JSON] TeamSearchVisibilityView)))))))
                        :<|> (Named
                                "set-search-visibility"
                                (Summary "Sets the search visibility for the whole team"
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamSearchVisibilityNotEnabled
                                             :> (CanThrow 'TeamNotFound
                                                 :> (CanThrow TeamFeatureError
                                                     :> (ZLocalUser
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("search-visibility"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           TeamSearchVisibilityView
                                                                         :> MultiVerb
                                                                              'PUT
                                                                              '[JSON]
                                                                              '[RespondEmpty
                                                                                  204
                                                                                  "Search visibility set"]
                                                                              ())))))))))))
                              :<|> (Named
                                      '("get", ValidateSAMLEmailsConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Get config for validateSAMLemails"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("validateSAMLemails"
                                                                           :> Get
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   ValidateSAMLEmailsConfig)))))))))))
                                    :<|> (Named
                                            '("get", DigitalSignaturesConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Get config for digitalSignatures"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("digitalSignatures"
                                                                                 :> Get
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         DigitalSignaturesConfig)))))))))))
                                          :<|> ((Named
                                                   '("get", AppLockConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary "Get config for appLock"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("appLock"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                AppLockConfig)))))))))))
                                                 :<|> Named
                                                        '("put", AppLockConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary "Put config for appLock"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("appLock"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              AppLockConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 AppLockConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", FileSharingConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for fileSharing"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("fileSharing"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      FileSharingConfig)))))))))))
                                                       :<|> Named
                                                              '("put", FileSharingConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for fileSharing"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("fileSharing"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    FileSharingConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       FileSharingConfig)))))))))))))))
                                                      :<|> (Named
                                                              '("get", ClassifiedDomainsConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Get config for classifiedDomains"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("classifiedDomains"
                                                                                                   :> Get
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           ClassifiedDomainsConfig)))))))))))
                                                            :<|> ((Named
                                                                     '("get",
                                                                       ConferenceCallingConfig)
                                                                     (Description ""
                                                                      :> (ZUser
                                                                          :> (Summary
                                                                                "Get config for conferenceCalling"
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("conferenceCalling"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  ConferenceCallingConfig)))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            ConferenceCallingConfig)
                                                                          (Description ""
                                                                           :> (ZUser
                                                                               :> (Summary
                                                                                     "Put config for conferenceCalling"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("conferenceCalling"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                ConferenceCallingConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   ConferenceCallingConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             SelfDeletingMessagesConfig)
                                                                           (Description ""
                                                                            :> (ZUser
                                                                                :> (Summary
                                                                                      "Get config for selfDeletingMessages"
                                                                                    :> (CanThrow
                                                                                          OperationDenied
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("selfDeletingMessages"
                                                                                                                :> Get
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        SelfDeletingMessagesConfig)))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  SelfDeletingMessagesConfig)
                                                                                (Description ""
                                                                                 :> (ZUser
                                                                                     :> (Summary
                                                                                           "Put config for selfDeletingMessages"
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("selfDeletingMessages"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (Feature
                                                                                                                                      SelfDeletingMessagesConfig)
                                                                                                                                 :> Put
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         SelfDeletingMessagesConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get",
                                                                                   GuestLinksConfig)
                                                                                 (Description ""
                                                                                  :> (ZUser
                                                                                      :> (Summary
                                                                                            "Get config for conversationGuestLinks"
                                                                                          :> (CanThrow
                                                                                                OperationDenied
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("conversationGuestLinks"
                                                                                                                      :> Get
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              GuestLinksConfig)))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        GuestLinksConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (ZUser
                                                                                           :> (Summary
                                                                                                 "Put config for conversationGuestLinks"
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 TeamFeatureError
                                                                                                               :> (CanThrowMany
                                                                                                                     '[]
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         (Feature
                                                                                                                                            GuestLinksConfig)
                                                                                                                                       :> Put
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               GuestLinksConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("get",
                                                                                         SndFactorPasswordChallengeConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (ZUser
                                                                                            :> (Summary
                                                                                                  "Get config for sndFactorPasswordChallenge"
                                                                                                :> (CanThrow
                                                                                                      OperationDenied
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("sndFactorPasswordChallenge"
                                                                                                                            :> Get
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    SndFactorPasswordChallengeConfig)))))))))))
                                                                                     :<|> Named
                                                                                            '("put",
                                                                                              SndFactorPasswordChallengeConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (ZUser
                                                                                                 :> (Summary
                                                                                                       "Put config for sndFactorPasswordChallenge"
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       TeamFeatureError
                                                                                                                     :> (CanThrowMany
                                                                                                                           '[]
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               (Feature
                                                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                                             :> Put
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     SndFactorPasswordChallengeConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("get",
                                                                                               MLSConfig)
                                                                                             (From
                                                                                                'V5
                                                                                              :> (Description
                                                                                                    ""
                                                                                                  :> (ZUser
                                                                                                      :> (Summary
                                                                                                            "Get config for mls"
                                                                                                          :> (CanThrow
                                                                                                                OperationDenied
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mls"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              MLSConfig))))))))))))
                                                                                           :<|> Named
                                                                                                  '("put",
                                                                                                    MLSConfig)
                                                                                                  (From
                                                                                                     'V5
                                                                                                   :> (Description
                                                                                                         ""
                                                                                                       :> (ZUser
                                                                                                           :> (Summary
                                                                                                                 "Put config for mls"
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("mls"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (Feature
                                                                                                                                                            MLSConfig)
                                                                                                                                                       :> Put
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               MLSConfig))))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("get",
                                                                                                     ExposeInvitationURLsToTeamAdminConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (ZUser
                                                                                                        :> (Summary
                                                                                                              "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                            :> (CanThrow
                                                                                                                  OperationDenied
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                        :> Get
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeature
                                                                                                                                                ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                                                                 :<|> Named
                                                                                                        '("put",
                                                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (ZUser
                                                                                                             :> (Summary
                                                                                                                   "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   TeamFeatureError
                                                                                                                                 :> (CanThrowMany
                                                                                                                                       '[]
                                                                                                                                     :> ("teams"
                                                                                                                                         :> (Capture
                                                                                                                                               "tid"
                                                                                                                                               TeamId
                                                                                                                                             :> ("features"
                                                                                                                                                 :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           (Feature
                                                                                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                         :> Put
                                                                                                                                                              '[JSON]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                                :<|> ((Named
                                                                                                         '("get",
                                                                                                           SearchVisibilityInboundConfig)
                                                                                                         (Description
                                                                                                            ""
                                                                                                          :> (ZUser
                                                                                                              :> (Summary
                                                                                                                    "Get config for searchVisibilityInbound"
                                                                                                                  :> (CanThrow
                                                                                                                        OperationDenied
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                'TeamNotFound
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("searchVisibilityInbound"
                                                                                                                                              :> Get
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeature
                                                                                                                                                      SearchVisibilityInboundConfig)))))))))))
                                                                                                       :<|> Named
                                                                                                              '("put",
                                                                                                                SearchVisibilityInboundConfig)
                                                                                                              (Description
                                                                                                                 ""
                                                                                                               :> (ZUser
                                                                                                                   :> (Summary
                                                                                                                         "Put config for searchVisibilityInbound"
                                                                                                                       :> (CanThrow
                                                                                                                             OperationDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'TeamNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         TeamFeatureError
                                                                                                                                       :> (CanThrowMany
                                                                                                                                             '[]
                                                                                                                                           :> ("teams"
                                                                                                                                               :> (Capture
                                                                                                                                                     "tid"
                                                                                                                                                     TeamId
                                                                                                                                                   :> ("features"
                                                                                                                                                       :> ("searchVisibilityInbound"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (Feature
                                                                                                                                                                    SearchVisibilityInboundConfig)
                                                                                                                                                               :> Put
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (LockableFeature
                                                                                                                                                                       SearchVisibilityInboundConfig)))))))))))))))
                                                                                                      :<|> ((Named
                                                                                                               '("get",
                                                                                                                 OutlookCalIntegrationConfig)
                                                                                                               (Description
                                                                                                                  ""
                                                                                                                :> (ZUser
                                                                                                                    :> (Summary
                                                                                                                          "Get config for outlookCalIntegration"
                                                                                                                        :> (CanThrow
                                                                                                                              OperationDenied
                                                                                                                            :> (CanThrow
                                                                                                                                  'NotATeamMember
                                                                                                                                :> (CanThrow
                                                                                                                                      'TeamNotFound
                                                                                                                                    :> ("teams"
                                                                                                                                        :> (Capture
                                                                                                                                              "tid"
                                                                                                                                              TeamId
                                                                                                                                            :> ("features"
                                                                                                                                                :> ("outlookCalIntegration"
                                                                                                                                                    :> Get
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeature
                                                                                                                                                            OutlookCalIntegrationConfig)))))))))))
                                                                                                             :<|> Named
                                                                                                                    '("put",
                                                                                                                      OutlookCalIntegrationConfig)
                                                                                                                    (Description
                                                                                                                       ""
                                                                                                                     :> (ZUser
                                                                                                                         :> (Summary
                                                                                                                               "Put config for outlookCalIntegration"
                                                                                                                             :> (CanThrow
                                                                                                                                   OperationDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           'TeamNotFound
                                                                                                                                         :> (CanThrow
                                                                                                                                               TeamFeatureError
                                                                                                                                             :> (CanThrowMany
                                                                                                                                                   '[]
                                                                                                                                                 :> ("teams"
                                                                                                                                                     :> (Capture
                                                                                                                                                           "tid"
                                                                                                                                                           TeamId
                                                                                                                                                         :> ("features"
                                                                                                                                                             :> ("outlookCalIntegration"
                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                       '[JSON]
                                                                                                                                                                       (Feature
                                                                                                                                                                          OutlookCalIntegrationConfig)
                                                                                                                                                                     :> Put
                                                                                                                                                                          '[JSON]
                                                                                                                                                                          (LockableFeature
                                                                                                                                                                             OutlookCalIntegrationConfig)))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get",
                                                                                                                      MlsE2EIdConfig)
                                                                                                                    (From
                                                                                                                       'V5
                                                                                                                     :> (Description
                                                                                                                           ""
                                                                                                                         :> (ZUser
                                                                                                                             :> (Summary
                                                                                                                                   "Get config for mlsE2EId"
                                                                                                                                 :> (CanThrow
                                                                                                                                       OperationDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("mlsE2EId"
                                                                                                                                                             :> Get
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     MlsE2EIdConfig))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "put-MlsE2EIdConfig@v5"
                                                                                                                          (From
                                                                                                                             'V5
                                                                                                                           :> (Until
                                                                                                                                 'V6
                                                                                                                               :> (ZUser
                                                                                                                                   :> (Summary
                                                                                                                                         "Put config for mlsE2EId"
                                                                                                                                       :> (CanThrow
                                                                                                                                             OperationDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("mlsE2EId"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (Feature
                                                                                                                                                                                    MlsE2EIdConfig)
                                                                                                                                                                               :> Put
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       MlsE2EIdConfig)))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("put",
                                                                                                                                  MlsE2EIdConfig)
                                                                                                                                (From
                                                                                                                                   'V6
                                                                                                                                 :> (Description
                                                                                                                                       ""
                                                                                                                                     :> (ZUser
                                                                                                                                         :> (Summary
                                                                                                                                               "Put config for mlsE2EId"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   OperationDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("mlsE2EId"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (Feature
                                                                                                                                                                                          MlsE2EIdConfig)
                                                                                                                                                                                     :> Put
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             MlsE2EIdConfig)))))))))))))))
                                                                                                                              :<|> ((Named
                                                                                                                                       '("get",
                                                                                                                                         MlsMigrationConfig)
                                                                                                                                       (From
                                                                                                                                          'V5
                                                                                                                                        :> (Description
                                                                                                                                              ""
                                                                                                                                            :> (ZUser
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for mlsMigration"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          OperationDenied
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("mlsMigration"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        MlsMigrationConfig))))))))))))
                                                                                                                                     :<|> Named
                                                                                                                                            '("put",
                                                                                                                                              MlsMigrationConfig)
                                                                                                                                            (From
                                                                                                                                               'V5
                                                                                                                                             :> (Description
                                                                                                                                                   ""
                                                                                                                                                 :> (ZUser
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Put config for mlsMigration"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               OperationDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("mlsMigration"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (Feature
                                                                                                                                                                                                      MlsMigrationConfig)
                                                                                                                                                                                                 :> Put
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         MlsMigrationConfig))))))))))))))))
                                                                                                                                    :<|> ((Named
                                                                                                                                             '("get",
                                                                                                                                               EnforceFileDownloadLocationConfig)
                                                                                                                                             (From
                                                                                                                                                'V5
                                                                                                                                              :> (Description
                                                                                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                  :> (ZUser
                                                                                                                                                      :> (Summary
                                                                                                                                                            "Get config for enforceFileDownloadLocation"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                OperationDenied
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              EnforceFileDownloadLocationConfig))))))))))))
                                                                                                                                           :<|> Named
                                                                                                                                                  '("put",
                                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                                                  (From
                                                                                                                                                     'V5
                                                                                                                                                   :> (Description
                                                                                                                                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                       :> (ZUser
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Put config for enforceFileDownloadLocation"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     OperationDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 TeamFeatureError
                                                                                                                                                                               :> (CanThrowMany
                                                                                                                                                                                     '[]
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> ("enforceFileDownloadLocation"
                                                                                                                                                                                                   :> (ReqBody
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (Feature
                                                                                                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                       :> Put
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get",
                                                                                                                                                    LimitedEventFanoutConfig)
                                                                                                                                                  (From
                                                                                                                                                     'V5
                                                                                                                                                   :> (Description
                                                                                                                                                         ""
                                                                                                                                                       :> (ZUser
                                                                                                                                                           :> (Summary
                                                                                                                                                                 "Get config for limitedEventFanout"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     OperationDenied
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("teams"
                                                                                                                                                                               :> (Capture
                                                                                                                                                                                     "tid"
                                                                                                                                                                                     TeamId
                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                                                                           :> Get
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   LimitedEventFanoutConfig))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-all-feature-configs-for-user"
                                                                                                                                                        (Summary
                                                                                                                                                           "Gets feature configs for a user"
                                                                                                                                                         :> (Description
                                                                                                                                                               "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                                                             :> (DescriptionOAuthScope
                                                                                                                                                                   'ReadFeatureConfigs
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> Get
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          AllTeamFeatures))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              "get-all-feature-configs-for-team"
                                                                                                                                                              (Summary
                                                                                                                                                                 "Gets feature configs for a team"
                                                                                                                                                               :> (Description
                                                                                                                                                                     "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             OperationDenied
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                               :> (ZLocalUser
                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                             "tid"
                                                                                                                                                                                             TeamId
                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    AllTeamFeatures)))))))))
                                                                                                                                                            :<|> ((Named
                                                                                                                                                                     '("get-deprecated",
                                                                                                                                                                       SearchVisibilityAvailableConfig)
                                                                                                                                                                     (ZUser
                                                                                                                                                                      :> (Summary
                                                                                                                                                                            "[deprecated] Get config for searchVisibility"
                                                                                                                                                                          :> (Until
                                                                                                                                                                                'V2
                                                                                                                                                                              :> (Description
                                                                                                                                                                                    "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                                        "tid"
                                                                                                                                                                                                        TeamId
                                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                                          :> ("search-visibility"
                                                                                                                                                                                                              :> Get
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                      SearchVisibilityAvailableConfig))))))))))))
                                                                                                                                                                   :<|> (Named
                                                                                                                                                                           '("put-deprecated",
                                                                                                                                                                             SearchVisibilityAvailableConfig)
                                                                                                                                                                           (ZUser
                                                                                                                                                                            :> (Summary
                                                                                                                                                                                  "[deprecated] Get config for searchVisibility"
                                                                                                                                                                                :> (Until
                                                                                                                                                                                      'V2
                                                                                                                                                                                    :> (Description
                                                                                                                                                                                          "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                          TeamFeatureError
                                                                                                                                                                                                        :> ("teams"
                                                                                                                                                                                                            :> (Capture
                                                                                                                                                                                                                  "tid"
                                                                                                                                                                                                                  TeamId
                                                                                                                                                                                                                :> ("features"
                                                                                                                                                                                                                    :> ("search-visibility"
                                                                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (Feature
                                                                                                                                                                                                                                 SearchVisibilityAvailableConfig)
                                                                                                                                                                                                                            :> Put
                                                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                                                    SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                                                                         :<|> (Named
                                                                                                                                                                                 '("get-deprecated",
                                                                                                                                                                                   ValidateSAMLEmailsConfig)
                                                                                                                                                                                 (ZUser
                                                                                                                                                                                  :> (Summary
                                                                                                                                                                                        "[deprecated] Get config for validateSAMLemails"
                                                                                                                                                                                      :> (Until
                                                                                                                                                                                            'V2
                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                          :> ("teams"
                                                                                                                                                                                                              :> (Capture
                                                                                                                                                                                                                    "tid"
                                                                                                                                                                                                                    TeamId
                                                                                                                                                                                                                  :> ("features"
                                                                                                                                                                                                                      :> ("validate-saml-emails"
                                                                                                                                                                                                                          :> Get
                                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                                                                  ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                                                               :<|> Named
                                                                                                                                                                                      '("get-deprecated",
                                                                                                                                                                                        DigitalSignaturesConfig)
                                                                                                                                                                                      (ZUser
                                                                                                                                                                                       :> (Summary
                                                                                                                                                                                             "[deprecated] Get config for digitalSignatures"
                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                 'V2
                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                     "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("teams"
                                                                                                                                                                                                                   :> (Capture
                                                                                                                                                                                                                         "tid"
                                                                                                                                                                                                                         TeamId
                                                                                                                                                                                                                       :> ("features"
                                                                                                                                                                                                                           :> ("digital-signatures"
                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                       DigitalSignaturesConfig)))))))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            LegalholdConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature legalhold"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("legalhold"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   LegalholdConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  SSOConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature sso"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("sso"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         SSOConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        SearchVisibilityAvailableConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("searchVisibility"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               SearchVisibilityAvailableConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              ValidateSAMLEmailsConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("validateSAMLemails"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    DigitalSignaturesConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("digitalSignatures"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           DigitalSignaturesConfig))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        '("get-config",
                                                                                                                                                                                                          AppLockConfig)
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "[deprecated] Get feature config for feature appLock"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                                                                     :> ("appLock"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                 AppLockConfig))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              '("get-config",
                                                                                                                                                                                                                FileSharingConfig)
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                                                                           :> ("fileSharing"
                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                                       FileSharingConfig))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    '("get-config",
                                                                                                                                                                                                                      ClassifiedDomainsConfig)
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                                                                 :> ("classifiedDomains"
                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                                             ClassifiedDomainsConfig))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          '("get-config",
                                                                                                                                                                                                                            ConferenceCallingConfig)
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                                                                       :> ("conferenceCalling"
                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                                                                   ConferenceCallingConfig))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                '("get-config",
                                                                                                                                                                                                                                  SelfDeletingMessagesConfig)
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                                                                             :> ("selfDeletingMessages"
                                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                                                                         SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                                                                        GuestLinksConfig)
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                                                                               GuestLinksConfig))))))))))
                                                                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                                                                              SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                                                            (Summary
                                                                                                                                                                                                                                               "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                                                                   'V2
                                                                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                                                                     SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                                                          :<|> Named
                                                                                                                                                                                                                                                 '("get-config",
                                                                                                                                                                                                                                                   MLSConfig)
                                                                                                                                                                                                                                                 (Summary
                                                                                                                                                                                                                                                    "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                                                                  :> (Until
                                                                                                                                                                                                                                                        'V2
                                                                                                                                                                                                                                                      :> (Description
                                                                                                                                                                                                                                                            "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                                          :> (ZUser
                                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                                                                                          :> ("feature-configs"
                                                                                                                                                                                                                                                                              :> ("mls"
                                                                                                                                                                                                                                                                                  :> Get
                                                                                                                                                                                                                                                                                       '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     '("get", LegalholdConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for legalhold"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("legalhold"
                                          :> Get '[JSON] (LockableFeature LegalholdConfig)))))))))))
   :<|> Named
          '("put", LegalholdConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for legalhold"
                   :> (CanThrow OperationDenied
                       :> (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)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), 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", LegalholdConfig)
     (Description (FeatureAPIDesc LegalholdConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol "Get config for " (FeatureSymbol LegalholdConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol LegalholdConfig
                                          :> Get '[JSON] (LockableFeature LegalholdConfig)))))))))))
   :<|> Named
          '("put", LegalholdConfig)
          (Description (FeatureAPIDesc LegalholdConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol "Put config for " (FeatureSymbol LegalholdConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors LegalholdConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol LegalholdConfig
                                                       :> (ReqBody '[JSON] (Feature LegalholdConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", LegalholdConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for legalhold"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("legalhold"
                                          :> Get '[JSON] (LockableFeature LegalholdConfig)))))))))))
   :<|> Named
          '("put", LegalholdConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for legalhold"
                   :> (CanThrow OperationDenied
                       :> (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)))))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), 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", SearchVisibilityAvailableConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for searchVisibility"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("searchVisibility"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      SearchVisibilityAvailableConfig)))))))))))
       :<|> Named
              '("put", SearchVisibilityAvailableConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for searchVisibility"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("searchVisibility"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    SearchVisibilityAvailableConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       SearchVisibilityAvailableConfig)))))))))))))))
      :<|> (Named
              "get-search-visibility"
              (Summary "Shows the value for search visibility"
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (ZLocalUser
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("search-visibility"
                                       :> Get '[JSON] TeamSearchVisibilityView)))))))
            :<|> (Named
                    "set-search-visibility"
                    (Summary "Sets the search visibility for the whole team"
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamSearchVisibilityNotEnabled
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (ZLocalUser
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("search-visibility"
                                                         :> (ReqBody
                                                               '[JSON] TeamSearchVisibilityView
                                                             :> MultiVerb
                                                                  'PUT
                                                                  '[JSON]
                                                                  '[RespondEmpty
                                                                      204 "Search visibility set"]
                                                                  ())))))))))))
                  :<|> (Named
                          '("get", ValidateSAMLEmailsConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Get config for validateSAMLemails"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("validateSAMLemails"
                                                               :> Get
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       ValidateSAMLEmailsConfig)))))))))))
                        :<|> (Named
                                '("get", DigitalSignaturesConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Get config for digitalSignatures"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("digitalSignatures"
                                                                     :> Get
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             DigitalSignaturesConfig)))))))))))
                              :<|> ((Named
                                       '("get", AppLockConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for appLock"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("appLock"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    AppLockConfig)))))))))))
                                     :<|> Named
                                            '("put", AppLockConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Put config for appLock"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("appLock"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  AppLockConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     AppLockConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", FileSharingConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary "Get config for fileSharing"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("fileSharing"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          FileSharingConfig)))))))))))
                                           :<|> Named
                                                  '("put", FileSharingConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary "Put config for fileSharing"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("fileSharing"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        FileSharingConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           FileSharingConfig)))))))))))))))
                                          :<|> (Named
                                                  '("get", ClassifiedDomainsConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Get config for classifiedDomains"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("classifiedDomains"
                                                                                       :> Get
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               ClassifiedDomainsConfig)))))))))))
                                                :<|> ((Named
                                                         '("get", ConferenceCallingConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for conferenceCalling"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("conferenceCalling"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      ConferenceCallingConfig)))))))))))
                                                       :<|> Named
                                                              '("put", ConferenceCallingConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for conferenceCalling"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("conferenceCalling"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    ConferenceCallingConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       ConferenceCallingConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get", SelfDeletingMessagesConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for selfDeletingMessages"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("selfDeletingMessages"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            SelfDeletingMessagesConfig)))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      SelfDeletingMessagesConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for selfDeletingMessages"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("selfDeletingMessages"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          SelfDeletingMessagesConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             SelfDeletingMessagesConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get", GuestLinksConfig)
                                                                     (Description ""
                                                                      :> (ZUser
                                                                          :> (Summary
                                                                                "Get config for conversationGuestLinks"
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("conversationGuestLinks"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  GuestLinksConfig)))))))))))
                                                                   :<|> Named
                                                                          '("put", GuestLinksConfig)
                                                                          (Description ""
                                                                           :> (ZUser
                                                                               :> (Summary
                                                                                     "Put config for conversationGuestLinks"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                GuestLinksConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   GuestLinksConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             SndFactorPasswordChallengeConfig)
                                                                           (Description ""
                                                                            :> (ZUser
                                                                                :> (Summary
                                                                                      "Get config for sndFactorPasswordChallenge"
                                                                                    :> (CanThrow
                                                                                          OperationDenied
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("sndFactorPasswordChallenge"
                                                                                                                :> Get
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        SndFactorPasswordChallengeConfig)))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  SndFactorPasswordChallengeConfig)
                                                                                (Description ""
                                                                                 :> (ZUser
                                                                                     :> (Summary
                                                                                           "Put config for sndFactorPasswordChallenge"
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (Feature
                                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                                 :> Put
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         SndFactorPasswordChallengeConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get", MLSConfig)
                                                                                 (From 'V5
                                                                                  :> (Description ""
                                                                                      :> (ZUser
                                                                                          :> (Summary
                                                                                                "Get config for mls"
                                                                                              :> (CanThrow
                                                                                                    OperationDenied
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mls"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  MLSConfig))))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        MLSConfig)
                                                                                      (From 'V5
                                                                                       :> (Description
                                                                                             ""
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Put config for mls"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("mls"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (Feature
                                                                                                                                                MLSConfig)
                                                                                                                                           :> Put
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   MLSConfig))))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("get",
                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (ZUser
                                                                                            :> (Summary
                                                                                                  "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                :> (CanThrow
                                                                                                      OperationDenied
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                            :> Get
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                                                     :<|> Named
                                                                                            '("put",
                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (ZUser
                                                                                                 :> (Summary
                                                                                                       "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       TeamFeatureError
                                                                                                                     :> (CanThrowMany
                                                                                                                           '[]
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               (Feature
                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                             :> Put
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("get",
                                                                                               SearchVisibilityInboundConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (ZUser
                                                                                                  :> (Summary
                                                                                                        "Get config for searchVisibilityInbound"
                                                                                                      :> (CanThrow
                                                                                                            OperationDenied
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("searchVisibilityInbound"
                                                                                                                                  :> Get
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          SearchVisibilityInboundConfig)))))))))))
                                                                                           :<|> Named
                                                                                                  '("put",
                                                                                                    SearchVisibilityInboundConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (ZUser
                                                                                                       :> (Summary
                                                                                                             "Put config for searchVisibilityInbound"
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             TeamFeatureError
                                                                                                                           :> (CanThrowMany
                                                                                                                                 '[]
                                                                                                                               :> ("teams"
                                                                                                                                   :> (Capture
                                                                                                                                         "tid"
                                                                                                                                         TeamId
                                                                                                                                       :> ("features"
                                                                                                                                           :> ("searchVisibilityInbound"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     (Feature
                                                                                                                                                        SearchVisibilityInboundConfig)
                                                                                                                                                   :> Put
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           SearchVisibilityInboundConfig)))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("get",
                                                                                                     OutlookCalIntegrationConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (ZUser
                                                                                                        :> (Summary
                                                                                                              "Get config for outlookCalIntegration"
                                                                                                            :> (CanThrow
                                                                                                                  OperationDenied
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("outlookCalIntegration"
                                                                                                                                        :> Get
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeature
                                                                                                                                                OutlookCalIntegrationConfig)))))))))))
                                                                                                 :<|> Named
                                                                                                        '("put",
                                                                                                          OutlookCalIntegrationConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (ZUser
                                                                                                             :> (Summary
                                                                                                                   "Put config for outlookCalIntegration"
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   TeamFeatureError
                                                                                                                                 :> (CanThrowMany
                                                                                                                                       '[]
                                                                                                                                     :> ("teams"
                                                                                                                                         :> (Capture
                                                                                                                                               "tid"
                                                                                                                                               TeamId
                                                                                                                                             :> ("features"
                                                                                                                                                 :> ("outlookCalIntegration"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           (Feature
                                                                                                                                                              OutlookCalIntegrationConfig)
                                                                                                                                                         :> Put
                                                                                                                                                              '[JSON]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 OutlookCalIntegrationConfig)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get",
                                                                                                          MlsE2EIdConfig)
                                                                                                        (From
                                                                                                           'V5
                                                                                                         :> (Description
                                                                                                               ""
                                                                                                             :> (ZUser
                                                                                                                 :> (Summary
                                                                                                                       "Get config for mlsE2EId"
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("mlsE2EId"
                                                                                                                                                 :> Get
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MlsE2EIdConfig))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "put-MlsE2EIdConfig@v5"
                                                                                                              (From
                                                                                                                 'V5
                                                                                                               :> (Until
                                                                                                                     'V6
                                                                                                                   :> (ZUser
                                                                                                                       :> (Summary
                                                                                                                             "Put config for mlsE2EId"
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("mlsE2EId"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (Feature
                                                                                                                                                                        MlsE2EIdConfig)
                                                                                                                                                                   :> Put
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("put",
                                                                                                                      MlsE2EIdConfig)
                                                                                                                    (From
                                                                                                                       'V6
                                                                                                                     :> (Description
                                                                                                                           ""
                                                                                                                         :> (ZUser
                                                                                                                             :> (Summary
                                                                                                                                   "Put config for mlsE2EId"
                                                                                                                                 :> (CanThrow
                                                                                                                                       OperationDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("mlsE2EId"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (Feature
                                                                                                                                                                              MlsE2EIdConfig)
                                                                                                                                                                         :> Put
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 MlsE2EIdConfig)))))))))))))))
                                                                                                                  :<|> ((Named
                                                                                                                           '("get",
                                                                                                                             MlsMigrationConfig)
                                                                                                                           (From
                                                                                                                              'V5
                                                                                                                            :> (Description
                                                                                                                                  ""
                                                                                                                                :> (ZUser
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for mlsMigration"
                                                                                                                                        :> (CanThrow
                                                                                                                                              OperationDenied
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("mlsMigration"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MlsMigrationConfig))))))))))))
                                                                                                                         :<|> Named
                                                                                                                                '("put",
                                                                                                                                  MlsMigrationConfig)
                                                                                                                                (From
                                                                                                                                   'V5
                                                                                                                                 :> (Description
                                                                                                                                       ""
                                                                                                                                     :> (ZUser
                                                                                                                                         :> (Summary
                                                                                                                                               "Put config for mlsMigration"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   OperationDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("mlsMigration"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (Feature
                                                                                                                                                                                          MlsMigrationConfig)
                                                                                                                                                                                     :> Put
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             MlsMigrationConfig))))))))))))))))
                                                                                                                        :<|> ((Named
                                                                                                                                 '("get",
                                                                                                                                   EnforceFileDownloadLocationConfig)
                                                                                                                                 (From
                                                                                                                                    'V5
                                                                                                                                  :> (Description
                                                                                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                      :> (ZUser
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for enforceFileDownloadLocation"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    OperationDenied
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  EnforceFileDownloadLocationConfig))))))))))))
                                                                                                                               :<|> Named
                                                                                                                                      '("put",
                                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                                      (From
                                                                                                                                         'V5
                                                                                                                                       :> (Description
                                                                                                                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                           :> (ZUser
                                                                                                                                               :> (Summary
                                                                                                                                                     "Put config for enforceFileDownloadLocation"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         OperationDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("enforceFileDownloadLocation"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (Feature
                                                                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                                                                           :> Put
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get",
                                                                                                                                        LimitedEventFanoutConfig)
                                                                                                                                      (From
                                                                                                                                         'V5
                                                                                                                                       :> (Description
                                                                                                                                             ""
                                                                                                                                           :> (ZUser
                                                                                                                                               :> (Summary
                                                                                                                                                     "Get config for limitedEventFanout"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         OperationDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("teams"
                                                                                                                                                                   :> (Capture
                                                                                                                                                                         "tid"
                                                                                                                                                                         TeamId
                                                                                                                                                                       :> ("features"
                                                                                                                                                                           :> ("limitedEventFanout"
                                                                                                                                                                               :> Get
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       LimitedEventFanoutConfig))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-all-feature-configs-for-user"
                                                                                                                                            (Summary
                                                                                                                                               "Gets feature configs for a user"
                                                                                                                                             :> (Description
                                                                                                                                                   "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                       'ReadFeatureConfigs
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> Get
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              AllTeamFeatures))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-all-feature-configs-for-team"
                                                                                                                                                  (Summary
                                                                                                                                                     "Gets feature configs for a team"
                                                                                                                                                   :> (Description
                                                                                                                                                         "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 OperationDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        AllTeamFeatures)))))))))
                                                                                                                                                :<|> ((Named
                                                                                                                                                         '("get-deprecated",
                                                                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                                                                         (ZUser
                                                                                                                                                          :> (Summary
                                                                                                                                                                "[deprecated] Get config for searchVisibility"
                                                                                                                                                              :> (Until
                                                                                                                                                                    'V2
                                                                                                                                                                  :> (Description
                                                                                                                                                                        "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                OperationDenied
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                            "tid"
                                                                                                                                                                                            TeamId
                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                              :> ("search-visibility"
                                                                                                                                                                                                  :> Get
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          SearchVisibilityAvailableConfig))))))))))))
                                                                                                                                                       :<|> (Named
                                                                                                                                                               '("put-deprecated",
                                                                                                                                                                 SearchVisibilityAvailableConfig)
                                                                                                                                                               (ZUser
                                                                                                                                                                :> (Summary
                                                                                                                                                                      "[deprecated] Get config for searchVisibility"
                                                                                                                                                                    :> (Until
                                                                                                                                                                          'V2
                                                                                                                                                                        :> (Description
                                                                                                                                                                              "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              TeamFeatureError
                                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                                :> (Capture
                                                                                                                                                                                                      "tid"
                                                                                                                                                                                                      TeamId
                                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                                        :> ("search-visibility"
                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (Feature
                                                                                                                                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                                                                                                                                :> Put
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                                                        SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                                                             :<|> (Named
                                                                                                                                                                     '("get-deprecated",
                                                                                                                                                                       ValidateSAMLEmailsConfig)
                                                                                                                                                                     (ZUser
                                                                                                                                                                      :> (Summary
                                                                                                                                                                            "[deprecated] Get config for validateSAMLemails"
                                                                                                                                                                          :> (Until
                                                                                                                                                                                'V2
                                                                                                                                                                              :> (Description
                                                                                                                                                                                    "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                                        "tid"
                                                                                                                                                                                                        TeamId
                                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                                          :> ("validate-saml-emails"
                                                                                                                                                                                                              :> Get
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                      ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                                                   :<|> Named
                                                                                                                                                                          '("get-deprecated",
                                                                                                                                                                            DigitalSignaturesConfig)
                                                                                                                                                                          (ZUser
                                                                                                                                                                           :> (Summary
                                                                                                                                                                                 "[deprecated] Get config for digitalSignatures"
                                                                                                                                                                               :> (Until
                                                                                                                                                                                     'V2
                                                                                                                                                                                   :> (Description
                                                                                                                                                                                         "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                             "tid"
                                                                                                                                                                                                             TeamId
                                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                                               :> ("digital-signatures"
                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           DigitalSignaturesConfig)))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                LegalholdConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature legalhold"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("legalhold"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       LegalholdConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      SSOConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature sso"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("sso"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             SSOConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            SearchVisibilityAvailableConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("searchVisibility"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   SearchVisibilityAvailableConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  ValidateSAMLEmailsConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("validateSAMLemails"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        DigitalSignaturesConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("digitalSignatures"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               DigitalSignaturesConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              AppLockConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature appLock"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("appLock"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     AppLockConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    FileSharingConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("fileSharing"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           FileSharingConfig))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        '("get-config",
                                                                                                                                                                                                          ClassifiedDomainsConfig)
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                                                                     :> ("classifiedDomains"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                 ClassifiedDomainsConfig))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              '("get-config",
                                                                                                                                                                                                                ConferenceCallingConfig)
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                                                                           :> ("conferenceCalling"
                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                                       ConferenceCallingConfig))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    '("get-config",
                                                                                                                                                                                                                      SelfDeletingMessagesConfig)
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                                                                 :> ("selfDeletingMessages"
                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                                             SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          '("get-config",
                                                                                                                                                                                                                            GuestLinksConfig)
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                                                                   GuestLinksConfig))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                '("get-config",
                                                                                                                                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                                                                         SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                                              :<|> Named
                                                                                                                                                                                                                                     '("get-config",
                                                                                                                                                                                                                                       MLSConfig)
                                                                                                                                                                                                                                     (Summary
                                                                                                                                                                                                                                        "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                                                      :> (Until
                                                                                                                                                                                                                                            'V2
                                                                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                                                                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                              :> (ZUser
                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                                                                              :> ("feature-configs"
                                                                                                                                                                                                                                                                  :> ("mls"
                                                                                                                                                                                                                                                                      :> Get
                                                                                                                                                                                                                                                                           '[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
         '("get", LegalholdConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for legalhold"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("legalhold"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature LegalholdConfig)))))))))))
       :<|> Named
              '("put", LegalholdConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for legalhold"
                       :> (CanThrow OperationDenied
                           :> (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
               '("get", SearchVisibilityAvailableConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for searchVisibility"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("searchVisibility"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            SearchVisibilityAvailableConfig)))))))))))
             :<|> Named
                    '("put", SearchVisibilityAvailableConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for searchVisibility"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("searchVisibility"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          SearchVisibilityAvailableConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             SearchVisibilityAvailableConfig)))))))))))))))
            :<|> (Named
                    "get-search-visibility"
                    (Summary "Shows the value for search visibility"
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (ZLocalUser
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("search-visibility"
                                             :> Get '[JSON] TeamSearchVisibilityView)))))))
                  :<|> (Named
                          "set-search-visibility"
                          (Summary "Sets the search visibility for the whole team"
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamSearchVisibilityNotEnabled
                                       :> (CanThrow 'TeamNotFound
                                           :> (CanThrow TeamFeatureError
                                               :> (ZLocalUser
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("search-visibility"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     TeamSearchVisibilityView
                                                                   :> MultiVerb
                                                                        'PUT
                                                                        '[JSON]
                                                                        '[RespondEmpty
                                                                            204
                                                                            "Search visibility set"]
                                                                        ())))))))))))
                        :<|> (Named
                                '("get", ValidateSAMLEmailsConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Get config for validateSAMLemails"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("validateSAMLemails"
                                                                     :> Get
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             ValidateSAMLEmailsConfig)))))))))))
                              :<|> (Named
                                      '("get", DigitalSignaturesConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Get config for digitalSignatures"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("digitalSignatures"
                                                                           :> Get
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   DigitalSignaturesConfig)))))))))))
                                    :<|> ((Named
                                             '("get", AppLockConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary "Get config for appLock"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("appLock"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          AppLockConfig)))))))))))
                                           :<|> Named
                                                  '("put", AppLockConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary "Put config for appLock"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("appLock"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        AppLockConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           AppLockConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", FileSharingConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary "Get config for fileSharing"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("fileSharing"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                FileSharingConfig)))))))))))
                                                 :<|> Named
                                                        '("put", FileSharingConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for fileSharing"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("fileSharing"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              FileSharingConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 FileSharingConfig)))))))))))))))
                                                :<|> (Named
                                                        '("get", ClassifiedDomainsConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Get config for classifiedDomains"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("classifiedDomains"
                                                                                             :> Get
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     ClassifiedDomainsConfig)))))))))))
                                                      :<|> ((Named
                                                               '("get", ConferenceCallingConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for conferenceCalling"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("conferenceCalling"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            ConferenceCallingConfig)))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      ConferenceCallingConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for conferenceCalling"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("conferenceCalling"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          ConferenceCallingConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             ConferenceCallingConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get",
                                                                       SelfDeletingMessagesConfig)
                                                                     (Description ""
                                                                      :> (ZUser
                                                                          :> (Summary
                                                                                "Get config for selfDeletingMessages"
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("selfDeletingMessages"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  SelfDeletingMessagesConfig)))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            SelfDeletingMessagesConfig)
                                                                          (Description ""
                                                                           :> (ZUser
                                                                               :> (Summary
                                                                                     "Put config for selfDeletingMessages"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("selfDeletingMessages"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                SelfDeletingMessagesConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   SelfDeletingMessagesConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             GuestLinksConfig)
                                                                           (Description ""
                                                                            :> (ZUser
                                                                                :> (Summary
                                                                                      "Get config for conversationGuestLinks"
                                                                                    :> (CanThrow
                                                                                          OperationDenied
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("conversationGuestLinks"
                                                                                                                :> Get
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        GuestLinksConfig)))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  GuestLinksConfig)
                                                                                (Description ""
                                                                                 :> (ZUser
                                                                                     :> (Summary
                                                                                           "Put config for conversationGuestLinks"
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (Feature
                                                                                                                                      GuestLinksConfig)
                                                                                                                                 :> Put
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         GuestLinksConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get",
                                                                                   SndFactorPasswordChallengeConfig)
                                                                                 (Description ""
                                                                                  :> (ZUser
                                                                                      :> (Summary
                                                                                            "Get config for sndFactorPasswordChallenge"
                                                                                          :> (CanThrow
                                                                                                OperationDenied
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("sndFactorPasswordChallenge"
                                                                                                                      :> Get
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              SndFactorPasswordChallengeConfig)))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        SndFactorPasswordChallengeConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (ZUser
                                                                                           :> (Summary
                                                                                                 "Put config for sndFactorPasswordChallenge"
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 TeamFeatureError
                                                                                                               :> (CanThrowMany
                                                                                                                     '[]
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         (Feature
                                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                                       :> Put
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               SndFactorPasswordChallengeConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("get",
                                                                                         MLSConfig)
                                                                                       (From 'V5
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (ZUser
                                                                                                :> (Summary
                                                                                                      "Get config for mls"
                                                                                                    :> (CanThrow
                                                                                                          OperationDenied
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mls"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        MLSConfig))))))))))))
                                                                                     :<|> Named
                                                                                            '("put",
                                                                                              MLSConfig)
                                                                                            (From
                                                                                               'V5
                                                                                             :> (Description
                                                                                                   ""
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Put config for mls"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("mls"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (Feature
                                                                                                                                                      MLSConfig)
                                                                                                                                                 :> Put
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MLSConfig))))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("get",
                                                                                               ExposeInvitationURLsToTeamAdminConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (ZUser
                                                                                                  :> (Summary
                                                                                                        "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                      :> (CanThrow
                                                                                                            OperationDenied
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                  :> Get
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                                                           :<|> Named
                                                                                                  '("put",
                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (ZUser
                                                                                                       :> (Summary
                                                                                                             "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             TeamFeatureError
                                                                                                                           :> (CanThrowMany
                                                                                                                                 '[]
                                                                                                                               :> ("teams"
                                                                                                                                   :> (Capture
                                                                                                                                         "tid"
                                                                                                                                         TeamId
                                                                                                                                       :> ("features"
                                                                                                                                           :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     (Feature
                                                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                                   :> Put
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("get",
                                                                                                     SearchVisibilityInboundConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (ZUser
                                                                                                        :> (Summary
                                                                                                              "Get config for searchVisibilityInbound"
                                                                                                            :> (CanThrow
                                                                                                                  OperationDenied
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("searchVisibilityInbound"
                                                                                                                                        :> Get
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeature
                                                                                                                                                SearchVisibilityInboundConfig)))))))))))
                                                                                                 :<|> Named
                                                                                                        '("put",
                                                                                                          SearchVisibilityInboundConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (ZUser
                                                                                                             :> (Summary
                                                                                                                   "Put config for searchVisibilityInbound"
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   TeamFeatureError
                                                                                                                                 :> (CanThrowMany
                                                                                                                                       '[]
                                                                                                                                     :> ("teams"
                                                                                                                                         :> (Capture
                                                                                                                                               "tid"
                                                                                                                                               TeamId
                                                                                                                                             :> ("features"
                                                                                                                                                 :> ("searchVisibilityInbound"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           (Feature
                                                                                                                                                              SearchVisibilityInboundConfig)
                                                                                                                                                         :> Put
                                                                                                                                                              '[JSON]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 SearchVisibilityInboundConfig)))))))))))))))
                                                                                                :<|> ((Named
                                                                                                         '("get",
                                                                                                           OutlookCalIntegrationConfig)
                                                                                                         (Description
                                                                                                            ""
                                                                                                          :> (ZUser
                                                                                                              :> (Summary
                                                                                                                    "Get config for outlookCalIntegration"
                                                                                                                  :> (CanThrow
                                                                                                                        OperationDenied
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                'TeamNotFound
                                                                                                                              :> ("teams"
                                                                                                                                  :> (Capture
                                                                                                                                        "tid"
                                                                                                                                        TeamId
                                                                                                                                      :> ("features"
                                                                                                                                          :> ("outlookCalIntegration"
                                                                                                                                              :> Get
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeature
                                                                                                                                                      OutlookCalIntegrationConfig)))))))))))
                                                                                                       :<|> Named
                                                                                                              '("put",
                                                                                                                OutlookCalIntegrationConfig)
                                                                                                              (Description
                                                                                                                 ""
                                                                                                               :> (ZUser
                                                                                                                   :> (Summary
                                                                                                                         "Put config for outlookCalIntegration"
                                                                                                                       :> (CanThrow
                                                                                                                             OperationDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     'TeamNotFound
                                                                                                                                   :> (CanThrow
                                                                                                                                         TeamFeatureError
                                                                                                                                       :> (CanThrowMany
                                                                                                                                             '[]
                                                                                                                                           :> ("teams"
                                                                                                                                               :> (Capture
                                                                                                                                                     "tid"
                                                                                                                                                     TeamId
                                                                                                                                                   :> ("features"
                                                                                                                                                       :> ("outlookCalIntegration"
                                                                                                                                                           :> (ReqBody
                                                                                                                                                                 '[JSON]
                                                                                                                                                                 (Feature
                                                                                                                                                                    OutlookCalIntegrationConfig)
                                                                                                                                                               :> Put
                                                                                                                                                                    '[JSON]
                                                                                                                                                                    (LockableFeature
                                                                                                                                                                       OutlookCalIntegrationConfig)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get",
                                                                                                                MlsE2EIdConfig)
                                                                                                              (From
                                                                                                                 'V5
                                                                                                               :> (Description
                                                                                                                     ""
                                                                                                                   :> (ZUser
                                                                                                                       :> (Summary
                                                                                                                             "Get config for mlsE2EId"
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("mlsE2EId"
                                                                                                                                                       :> Get
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               MlsE2EIdConfig))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "put-MlsE2EIdConfig@v5"
                                                                                                                    (From
                                                                                                                       'V5
                                                                                                                     :> (Until
                                                                                                                           'V6
                                                                                                                         :> (ZUser
                                                                                                                             :> (Summary
                                                                                                                                   "Put config for mlsE2EId"
                                                                                                                                 :> (CanThrow
                                                                                                                                       OperationDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("mlsE2EId"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (Feature
                                                                                                                                                                              MlsE2EIdConfig)
                                                                                                                                                                         :> Put
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 MlsE2EIdConfig)))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("put",
                                                                                                                            MlsE2EIdConfig)
                                                                                                                          (From
                                                                                                                             'V6
                                                                                                                           :> (Description
                                                                                                                                 ""
                                                                                                                               :> (ZUser
                                                                                                                                   :> (Summary
                                                                                                                                         "Put config for mlsE2EId"
                                                                                                                                       :> (CanThrow
                                                                                                                                             OperationDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("mlsE2EId"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (Feature
                                                                                                                                                                                    MlsE2EIdConfig)
                                                                                                                                                                               :> Put
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       MlsE2EIdConfig)))))))))))))))
                                                                                                                        :<|> ((Named
                                                                                                                                 '("get",
                                                                                                                                   MlsMigrationConfig)
                                                                                                                                 (From
                                                                                                                                    'V5
                                                                                                                                  :> (Description
                                                                                                                                        ""
                                                                                                                                      :> (ZUser
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for mlsMigration"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    OperationDenied
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("mlsMigration"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  MlsMigrationConfig))))))))))))
                                                                                                                               :<|> Named
                                                                                                                                      '("put",
                                                                                                                                        MlsMigrationConfig)
                                                                                                                                      (From
                                                                                                                                         'V5
                                                                                                                                       :> (Description
                                                                                                                                             ""
                                                                                                                                           :> (ZUser
                                                                                                                                               :> (Summary
                                                                                                                                                     "Put config for mlsMigration"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         OperationDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("mlsMigration"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (Feature
                                                                                                                                                                                                MlsMigrationConfig)
                                                                                                                                                                                           :> Put
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   MlsMigrationConfig))))))))))))))))
                                                                                                                              :<|> ((Named
                                                                                                                                       '("get",
                                                                                                                                         EnforceFileDownloadLocationConfig)
                                                                                                                                       (From
                                                                                                                                          'V5
                                                                                                                                        :> (Description
                                                                                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                            :> (ZUser
                                                                                                                                                :> (Summary
                                                                                                                                                      "Get config for enforceFileDownloadLocation"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          OperationDenied
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        EnforceFileDownloadLocationConfig))))))))))))
                                                                                                                                     :<|> Named
                                                                                                                                            '("put",
                                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                                            (From
                                                                                                                                               'V5
                                                                                                                                             :> (Description
                                                                                                                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                                 :> (ZUser
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Put config for enforceFileDownloadLocation"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               OperationDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           TeamFeatureError
                                                                                                                                                                         :> (CanThrowMany
                                                                                                                                                                               '[]
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> ("enforceFileDownloadLocation"
                                                                                                                                                                                             :> (ReqBody
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (Feature
                                                                                                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                                                                                                 :> Put
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get",
                                                                                                                                              LimitedEventFanoutConfig)
                                                                                                                                            (From
                                                                                                                                               'V5
                                                                                                                                             :> (Description
                                                                                                                                                   ""
                                                                                                                                                 :> (ZUser
                                                                                                                                                     :> (Summary
                                                                                                                                                           "Get config for limitedEventFanout"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               OperationDenied
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("teams"
                                                                                                                                                                         :> (Capture
                                                                                                                                                                               "tid"
                                                                                                                                                                               TeamId
                                                                                                                                                                             :> ("features"
                                                                                                                                                                                 :> ("limitedEventFanout"
                                                                                                                                                                                     :> Get
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             LimitedEventFanoutConfig))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-all-feature-configs-for-user"
                                                                                                                                                  (Summary
                                                                                                                                                     "Gets feature configs for a user"
                                                                                                                                                   :> (Description
                                                                                                                                                         "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                                                       :> (DescriptionOAuthScope
                                                                                                                                                             'ReadFeatureConfigs
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> Get
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    AllTeamFeatures))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        "get-all-feature-configs-for-team"
                                                                                                                                                        (Summary
                                                                                                                                                           "Gets feature configs for a team"
                                                                                                                                                         :> (Description
                                                                                                                                                               "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       OperationDenied
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                         :> (ZLocalUser
                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                       "tid"
                                                                                                                                                                                       TeamId
                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              AllTeamFeatures)))))))))
                                                                                                                                                      :<|> ((Named
                                                                                                                                                               '("get-deprecated",
                                                                                                                                                                 SearchVisibilityAvailableConfig)
                                                                                                                                                               (ZUser
                                                                                                                                                                :> (Summary
                                                                                                                                                                      "[deprecated] Get config for searchVisibility"
                                                                                                                                                                    :> (Until
                                                                                                                                                                          'V2
                                                                                                                                                                        :> (Description
                                                                                                                                                                              "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> ("teams"
                                                                                                                                                                                            :> (Capture
                                                                                                                                                                                                  "tid"
                                                                                                                                                                                                  TeamId
                                                                                                                                                                                                :> ("features"
                                                                                                                                                                                                    :> ("search-visibility"
                                                                                                                                                                                                        :> Get
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                SearchVisibilityAvailableConfig))))))))))))
                                                                                                                                                             :<|> (Named
                                                                                                                                                                     '("put-deprecated",
                                                                                                                                                                       SearchVisibilityAvailableConfig)
                                                                                                                                                                     (ZUser
                                                                                                                                                                      :> (Summary
                                                                                                                                                                            "[deprecated] Get config for searchVisibility"
                                                                                                                                                                          :> (Until
                                                                                                                                                                                'V2
                                                                                                                                                                              :> (Description
                                                                                                                                                                                    "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    TeamFeatureError
                                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                                            "tid"
                                                                                                                                                                                                            TeamId
                                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                                              :> ("search-visibility"
                                                                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (Feature
                                                                                                                                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                                                                                                                                      :> Put
                                                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                                                              SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                                                                   :<|> (Named
                                                                                                                                                                           '("get-deprecated",
                                                                                                                                                                             ValidateSAMLEmailsConfig)
                                                                                                                                                                           (ZUser
                                                                                                                                                                            :> (Summary
                                                                                                                                                                                  "[deprecated] Get config for validateSAMLemails"
                                                                                                                                                                                :> (Until
                                                                                                                                                                                      'V2
                                                                                                                                                                                    :> (Description
                                                                                                                                                                                          "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                    :> ("teams"
                                                                                                                                                                                                        :> (Capture
                                                                                                                                                                                                              "tid"
                                                                                                                                                                                                              TeamId
                                                                                                                                                                                                            :> ("features"
                                                                                                                                                                                                                :> ("validate-saml-emails"
                                                                                                                                                                                                                    :> Get
                                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                                                            ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                                                         :<|> Named
                                                                                                                                                                                '("get-deprecated",
                                                                                                                                                                                  DigitalSignaturesConfig)
                                                                                                                                                                                (ZUser
                                                                                                                                                                                 :> (Summary
                                                                                                                                                                                       "[deprecated] Get config for digitalSignatures"
                                                                                                                                                                                     :> (Until
                                                                                                                                                                                           'V2
                                                                                                                                                                                         :> (Description
                                                                                                                                                                                               "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("teams"
                                                                                                                                                                                                             :> (Capture
                                                                                                                                                                                                                   "tid"
                                                                                                                                                                                                                   TeamId
                                                                                                                                                                                                                 :> ("features"
                                                                                                                                                                                                                     :> ("digital-signatures"
                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                 DigitalSignaturesConfig)))))))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      LegalholdConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature legalhold"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("legalhold"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             LegalholdConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            SSOConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature sso"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("sso"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   SSOConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  SearchVisibilityAvailableConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("searchVisibility"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         SearchVisibilityAvailableConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        ValidateSAMLEmailsConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("validateSAMLemails"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              DigitalSignaturesConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("digitalSignatures"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     DigitalSignaturesConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    AppLockConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature appLock"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("appLock"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           AppLockConfig))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        '("get-config",
                                                                                                                                                                                                          FileSharingConfig)
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                                                                     :> ("fileSharing"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                 FileSharingConfig))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              '("get-config",
                                                                                                                                                                                                                ClassifiedDomainsConfig)
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                                                                           :> ("classifiedDomains"
                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                                       ClassifiedDomainsConfig))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    '("get-config",
                                                                                                                                                                                                                      ConferenceCallingConfig)
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                                                                 :> ("conferenceCalling"
                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                                             ConferenceCallingConfig))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          '("get-config",
                                                                                                                                                                                                                            SelfDeletingMessagesConfig)
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                                                                       :> ("selfDeletingMessages"
                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                                                                   SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                '("get-config",
                                                                                                                                                                                                                                  GuestLinksConfig)
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                                                                         GuestLinksConfig))))))))))
                                                                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                                                      (Summary
                                                                                                                                                                                                                                         "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                                                       :> (Until
                                                                                                                                                                                                                                             'V2
                                                                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                                                                               SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                                                                           '("get-config",
                                                                                                                                                                                                                                             MLSConfig)
                                                                                                                                                                                                                                           (Summary
                                                                                                                                                                                                                                              "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                                                            :> (Until
                                                                                                                                                                                                                                                  'V2
                                                                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                                                                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                                    :> (ZUser
                                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                                                                    :> ("feature-configs"
                                                                                                                                                                                                                                                                        :> ("mls"
                                                                                                                                                                                                                                                                            :> Get
                                                                                                                                                                                                                                                                                 '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     '("get", SearchVisibilityAvailableConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for searchVisibility"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("searchVisibility"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SearchVisibilityAvailableConfig)))))))))))
   :<|> Named
          '("put", SearchVisibilityAvailableConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for searchVisibility"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("searchVisibility"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature
                                                                SearchVisibilityAvailableConfig)
                                                           :> Put
                                                                '[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
     '("get", SearchVisibilityAvailableConfig)
     (Description (FeatureAPIDesc SearchVisibilityAvailableConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol
                   "Get config for " (FeatureSymbol SearchVisibilityAvailableConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol SearchVisibilityAvailableConfig
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SearchVisibilityAvailableConfig)))))))))))
   :<|> Named
          '("put", SearchVisibilityAvailableConfig)
          (Description (FeatureAPIDesc SearchVisibilityAvailableConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol
                        "Put config for " (FeatureSymbol SearchVisibilityAvailableConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors SearchVisibilityAvailableConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol SearchVisibilityAvailableConfig
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature
                                                                SearchVisibilityAvailableConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", SearchVisibilityAvailableConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for searchVisibility"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("searchVisibility"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SearchVisibilityAvailableConfig)))))))))))
   :<|> Named
          '("put", SearchVisibilityAvailableConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for searchVisibility"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("searchVisibility"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature
                                                                SearchVisibilityAvailableConfig)
                                                           :> Put
                                                                '[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
        "get-search-visibility"
        (Summary "Shows the value for search visibility"
         :> (CanThrow 'NotATeamMember
             :> (CanThrow OperationDenied
                 :> (ZLocalUser
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("search-visibility"
                                 :> Get '[JSON] TeamSearchVisibilityView)))))))
      :<|> (Named
              "set-search-visibility"
              (Summary "Sets the search visibility for the whole team"
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamSearchVisibilityNotEnabled
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (ZLocalUser
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("search-visibility"
                                                   :> (ReqBody '[JSON] TeamSearchVisibilityView
                                                       :> MultiVerb
                                                            'PUT
                                                            '[JSON]
                                                            '[RespondEmpty
                                                                204 "Search visibility set"]
                                                            ())))))))))))
            :<|> (Named
                    '("get", ValidateSAMLEmailsConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Get config for validateSAMLemails"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("validateSAMLemails"
                                                         :> Get
                                                              '[JSON]
                                                              (LockableFeature
                                                                 ValidateSAMLEmailsConfig)))))))))))
                  :<|> (Named
                          '("get", DigitalSignaturesConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Get config for digitalSignatures"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("digitalSignatures"
                                                               :> Get
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       DigitalSignaturesConfig)))))))))))
                        :<|> ((Named
                                 '("get", AppLockConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for appLock"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("appLock"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              AppLockConfig)))))))))))
                               :<|> Named
                                      '("put", AppLockConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for appLock"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("appLock"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            AppLockConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               AppLockConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", FileSharingConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for fileSharing"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("fileSharing"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    FileSharingConfig)))))))))))
                                     :<|> Named
                                            '("put", FileSharingConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Put config for fileSharing"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("fileSharing"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  FileSharingConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     FileSharingConfig)))))))))))))))
                                    :<|> (Named
                                            '("get", ClassifiedDomainsConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Get config for classifiedDomains"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("classifiedDomains"
                                                                                 :> Get
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         ClassifiedDomainsConfig)))))))))))
                                          :<|> ((Named
                                                   '("get", ConferenceCallingConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for conferenceCalling"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("conferenceCalling"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                ConferenceCallingConfig)))))))))))
                                                 :<|> Named
                                                        '("put", ConferenceCallingConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for conferenceCalling"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("conferenceCalling"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              ConferenceCallingConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 ConferenceCallingConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", SelfDeletingMessagesConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for selfDeletingMessages"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("selfDeletingMessages"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      SelfDeletingMessagesConfig)))))))))))
                                                       :<|> Named
                                                              '("put", SelfDeletingMessagesConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for selfDeletingMessages"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("selfDeletingMessages"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    SelfDeletingMessagesConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       SelfDeletingMessagesConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get", GuestLinksConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for conversationGuestLinks"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("conversationGuestLinks"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            GuestLinksConfig)))))))))))
                                                             :<|> Named
                                                                    '("put", GuestLinksConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for conversationGuestLinks"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("conversationGuestLinks"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          GuestLinksConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             GuestLinksConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get",
                                                                       SndFactorPasswordChallengeConfig)
                                                                     (Description ""
                                                                      :> (ZUser
                                                                          :> (Summary
                                                                                "Get config for sndFactorPasswordChallenge"
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("sndFactorPasswordChallenge"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  SndFactorPasswordChallengeConfig)))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            SndFactorPasswordChallengeConfig)
                                                                          (Description ""
                                                                           :> (ZUser
                                                                               :> (Summary
                                                                                     "Put config for sndFactorPasswordChallenge"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   SndFactorPasswordChallengeConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get", MLSConfig)
                                                                           (From 'V5
                                                                            :> (Description ""
                                                                                :> (ZUser
                                                                                    :> (Summary
                                                                                          "Get config for mls"
                                                                                        :> (CanThrow
                                                                                              OperationDenied
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mls"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            MLSConfig))))))))))))
                                                                         :<|> Named
                                                                                '("put", MLSConfig)
                                                                                (From 'V5
                                                                                 :> (Description ""
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Put config for mls"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("mls"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (Feature
                                                                                                                                          MLSConfig)
                                                                                                                                     :> Put
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             MLSConfig))))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get",
                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                 (Description ""
                                                                                  :> (ZUser
                                                                                      :> (Summary
                                                                                            "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                          :> (CanThrow
                                                                                                OperationDenied
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                      :> Get
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (ZUser
                                                                                           :> (Summary
                                                                                                 "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 TeamFeatureError
                                                                                                               :> (CanThrowMany
                                                                                                                     '[]
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         (Feature
                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                       :> Put
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("get",
                                                                                         SearchVisibilityInboundConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (ZUser
                                                                                            :> (Summary
                                                                                                  "Get config for searchVisibilityInbound"
                                                                                                :> (CanThrow
                                                                                                      OperationDenied
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("searchVisibilityInbound"
                                                                                                                            :> Get
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    SearchVisibilityInboundConfig)))))))))))
                                                                                     :<|> Named
                                                                                            '("put",
                                                                                              SearchVisibilityInboundConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (ZUser
                                                                                                 :> (Summary
                                                                                                       "Put config for searchVisibilityInbound"
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       TeamFeatureError
                                                                                                                     :> (CanThrowMany
                                                                                                                           '[]
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("searchVisibilityInbound"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               (Feature
                                                                                                                                                  SearchVisibilityInboundConfig)
                                                                                                                                             :> Put
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     SearchVisibilityInboundConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("get",
                                                                                               OutlookCalIntegrationConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (ZUser
                                                                                                  :> (Summary
                                                                                                        "Get config for outlookCalIntegration"
                                                                                                      :> (CanThrow
                                                                                                            OperationDenied
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("outlookCalIntegration"
                                                                                                                                  :> Get
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          OutlookCalIntegrationConfig)))))))))))
                                                                                           :<|> Named
                                                                                                  '("put",
                                                                                                    OutlookCalIntegrationConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (ZUser
                                                                                                       :> (Summary
                                                                                                             "Put config for outlookCalIntegration"
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             TeamFeatureError
                                                                                                                           :> (CanThrowMany
                                                                                                                                 '[]
                                                                                                                               :> ("teams"
                                                                                                                                   :> (Capture
                                                                                                                                         "tid"
                                                                                                                                         TeamId
                                                                                                                                       :> ("features"
                                                                                                                                           :> ("outlookCalIntegration"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     (Feature
                                                                                                                                                        OutlookCalIntegrationConfig)
                                                                                                                                                   :> Put
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           OutlookCalIntegrationConfig)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get",
                                                                                                    MlsE2EIdConfig)
                                                                                                  (From
                                                                                                     'V5
                                                                                                   :> (Description
                                                                                                         ""
                                                                                                       :> (ZUser
                                                                                                           :> (Summary
                                                                                                                 "Get config for mlsE2EId"
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("mlsE2EId"
                                                                                                                                           :> Get
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   MlsE2EIdConfig))))))))))))
                                                                                                :<|> (Named
                                                                                                        "put-MlsE2EIdConfig@v5"
                                                                                                        (From
                                                                                                           'V5
                                                                                                         :> (Until
                                                                                                               'V6
                                                                                                             :> (ZUser
                                                                                                                 :> (Summary
                                                                                                                       "Put config for mlsE2EId"
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("mlsE2EId"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (Feature
                                                                                                                                                                  MlsE2EIdConfig)
                                                                                                                                                             :> Put
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     MlsE2EIdConfig)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("put",
                                                                                                                MlsE2EIdConfig)
                                                                                                              (From
                                                                                                                 'V6
                                                                                                               :> (Description
                                                                                                                     ""
                                                                                                                   :> (ZUser
                                                                                                                       :> (Summary
                                                                                                                             "Put config for mlsE2EId"
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("mlsE2EId"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (Feature
                                                                                                                                                                        MlsE2EIdConfig)
                                                                                                                                                                   :> Put
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                                                                            :<|> ((Named
                                                                                                                     '("get",
                                                                                                                       MlsMigrationConfig)
                                                                                                                     (From
                                                                                                                        'V5
                                                                                                                      :> (Description
                                                                                                                            ""
                                                                                                                          :> (ZUser
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for mlsMigration"
                                                                                                                                  :> (CanThrow
                                                                                                                                        OperationDenied
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("mlsMigration"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MlsMigrationConfig))))))))))))
                                                                                                                   :<|> Named
                                                                                                                          '("put",
                                                                                                                            MlsMigrationConfig)
                                                                                                                          (From
                                                                                                                             'V5
                                                                                                                           :> (Description
                                                                                                                                 ""
                                                                                                                               :> (ZUser
                                                                                                                                   :> (Summary
                                                                                                                                         "Put config for mlsMigration"
                                                                                                                                       :> (CanThrow
                                                                                                                                             OperationDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("mlsMigration"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (Feature
                                                                                                                                                                                    MlsMigrationConfig)
                                                                                                                                                                               :> Put
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       MlsMigrationConfig))))))))))))))))
                                                                                                                  :<|> ((Named
                                                                                                                           '("get",
                                                                                                                             EnforceFileDownloadLocationConfig)
                                                                                                                           (From
                                                                                                                              'V5
                                                                                                                            :> (Description
                                                                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                :> (ZUser
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for enforceFileDownloadLocation"
                                                                                                                                        :> (CanThrow
                                                                                                                                              OperationDenied
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            EnforceFileDownloadLocationConfig))))))))))))
                                                                                                                         :<|> Named
                                                                                                                                '("put",
                                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                                                (From
                                                                                                                                   'V5
                                                                                                                                 :> (Description
                                                                                                                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                     :> (ZUser
                                                                                                                                         :> (Summary
                                                                                                                                               "Put config for enforceFileDownloadLocation"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   OperationDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (Feature
                                                                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                                                                     :> Put
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get",
                                                                                                                                  LimitedEventFanoutConfig)
                                                                                                                                (From
                                                                                                                                   'V5
                                                                                                                                 :> (Description
                                                                                                                                       ""
                                                                                                                                     :> (ZUser
                                                                                                                                         :> (Summary
                                                                                                                                               "Get config for limitedEventFanout"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   OperationDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("teams"
                                                                                                                                                             :> (Capture
                                                                                                                                                                   "tid"
                                                                                                                                                                   TeamId
                                                                                                                                                                 :> ("features"
                                                                                                                                                                     :> ("limitedEventFanout"
                                                                                                                                                                         :> Get
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 LimitedEventFanoutConfig))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-all-feature-configs-for-user"
                                                                                                                                      (Summary
                                                                                                                                         "Gets feature configs for a user"
                                                                                                                                       :> (Description
                                                                                                                                             "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                 'ReadFeatureConfigs
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> Get
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        AllTeamFeatures))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-all-feature-configs-for-team"
                                                                                                                                            (Summary
                                                                                                                                               "Gets feature configs for a team"
                                                                                                                                             :> (Description
                                                                                                                                                   "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           OperationDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'TeamNotFound
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  AllTeamFeatures)))))))))
                                                                                                                                          :<|> ((Named
                                                                                                                                                   '("get-deprecated",
                                                                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                                                                   (ZUser
                                                                                                                                                    :> (Summary
                                                                                                                                                          "[deprecated] Get config for searchVisibility"
                                                                                                                                                        :> (Until
                                                                                                                                                              'V2
                                                                                                                                                            :> (Description
                                                                                                                                                                  "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          OperationDenied
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                :> (Capture
                                                                                                                                                                                      "tid"
                                                                                                                                                                                      TeamId
                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                        :> ("search-visibility"
                                                                                                                                                                                            :> Get
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    SearchVisibilityAvailableConfig))))))))))))
                                                                                                                                                 :<|> (Named
                                                                                                                                                         '("put-deprecated",
                                                                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                                                                         (ZUser
                                                                                                                                                          :> (Summary
                                                                                                                                                                "[deprecated] Get config for searchVisibility"
                                                                                                                                                              :> (Until
                                                                                                                                                                    'V2
                                                                                                                                                                  :> (Description
                                                                                                                                                                        "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                OperationDenied
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        TeamFeatureError
                                                                                                                                                                                      :> ("teams"
                                                                                                                                                                                          :> (Capture
                                                                                                                                                                                                "tid"
                                                                                                                                                                                                TeamId
                                                                                                                                                                                              :> ("features"
                                                                                                                                                                                                  :> ("search-visibility"
                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (Feature
                                                                                                                                                                                                               SearchVisibilityAvailableConfig)
                                                                                                                                                                                                          :> Put
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                                                  SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                                                       :<|> (Named
                                                                                                                                                               '("get-deprecated",
                                                                                                                                                                 ValidateSAMLEmailsConfig)
                                                                                                                                                               (ZUser
                                                                                                                                                                :> (Summary
                                                                                                                                                                      "[deprecated] Get config for validateSAMLemails"
                                                                                                                                                                    :> (Until
                                                                                                                                                                          'V2
                                                                                                                                                                        :> (Description
                                                                                                                                                                              "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> ("teams"
                                                                                                                                                                                            :> (Capture
                                                                                                                                                                                                  "tid"
                                                                                                                                                                                                  TeamId
                                                                                                                                                                                                :> ("features"
                                                                                                                                                                                                    :> ("validate-saml-emails"
                                                                                                                                                                                                        :> Get
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                                             :<|> Named
                                                                                                                                                                    '("get-deprecated",
                                                                                                                                                                      DigitalSignaturesConfig)
                                                                                                                                                                    (ZUser
                                                                                                                                                                     :> (Summary
                                                                                                                                                                           "[deprecated] Get config for digitalSignatures"
                                                                                                                                                                         :> (Until
                                                                                                                                                                               'V2
                                                                                                                                                                             :> (Description
                                                                                                                                                                                   "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                       "tid"
                                                                                                                                                                                                       TeamId
                                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                                         :> ("digital-signatures"
                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     DigitalSignaturesConfig)))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          LegalholdConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature legalhold"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("legalhold"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 LegalholdConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                SSOConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature sso"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("sso"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       SSOConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      SearchVisibilityAvailableConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("searchVisibility"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             SearchVisibilityAvailableConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            ValidateSAMLEmailsConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("validateSAMLemails"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  DigitalSignaturesConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("digitalSignatures"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         DigitalSignaturesConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        AppLockConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature appLock"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("appLock"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               AppLockConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              FileSharingConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("fileSharing"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     FileSharingConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    ClassifiedDomainsConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("classifiedDomains"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           ClassifiedDomainsConfig))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        '("get-config",
                                                                                                                                                                                                          ConferenceCallingConfig)
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                                                                     :> ("conferenceCalling"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                 ConferenceCallingConfig))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              '("get-config",
                                                                                                                                                                                                                SelfDeletingMessagesConfig)
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                                                                           :> ("selfDeletingMessages"
                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                                       SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    '("get-config",
                                                                                                                                                                                                                      GuestLinksConfig)
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                                             GuestLinksConfig))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          '("get-config",
                                                                                                                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                                                                   SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                                        :<|> Named
                                                                                                                                                                                                                               '("get-config",
                                                                                                                                                                                                                                 MLSConfig)
                                                                                                                                                                                                                               (Summary
                                                                                                                                                                                                                                  "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                                                :> (Until
                                                                                                                                                                                                                                      'V2
                                                                                                                                                                                                                                    :> (Description
                                                                                                                                                                                                                                          "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                        :> (ZUser
                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                                                                        :> ("feature-configs"
                                                                                                                                                                                                                                                            :> ("mls"
                                                                                                                                                                                                                                                                :> Get
                                                                                                                                                                                                                                                                     '[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
         '("get", SearchVisibilityAvailableConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for searchVisibility"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("searchVisibility"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      SearchVisibilityAvailableConfig)))))))))))
       :<|> Named
              '("put", SearchVisibilityAvailableConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for searchVisibility"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("searchVisibility"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    SearchVisibilityAvailableConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       SearchVisibilityAvailableConfig)))))))))))))))
      :<|> (Named
              "get-search-visibility"
              (Summary "Shows the value for search visibility"
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (ZLocalUser
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("search-visibility"
                                       :> Get '[JSON] TeamSearchVisibilityView)))))))
            :<|> (Named
                    "set-search-visibility"
                    (Summary "Sets the search visibility for the whole team"
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamSearchVisibilityNotEnabled
                                 :> (CanThrow 'TeamNotFound
                                     :> (CanThrow TeamFeatureError
                                         :> (ZLocalUser
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("search-visibility"
                                                         :> (ReqBody
                                                               '[JSON] TeamSearchVisibilityView
                                                             :> MultiVerb
                                                                  'PUT
                                                                  '[JSON]
                                                                  '[RespondEmpty
                                                                      204 "Search visibility set"]
                                                                  ())))))))))))
                  :<|> (Named
                          '("get", ValidateSAMLEmailsConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Get config for validateSAMLemails"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("validateSAMLemails"
                                                               :> Get
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       ValidateSAMLEmailsConfig)))))))))))
                        :<|> (Named
                                '("get", DigitalSignaturesConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Get config for digitalSignatures"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("digitalSignatures"
                                                                     :> Get
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             DigitalSignaturesConfig)))))))))))
                              :<|> ((Named
                                       '("get", AppLockConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for appLock"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("appLock"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    AppLockConfig)))))))))))
                                     :<|> Named
                                            '("put", AppLockConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Put config for appLock"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("appLock"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  AppLockConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     AppLockConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", FileSharingConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary "Get config for fileSharing"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("fileSharing"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          FileSharingConfig)))))))))))
                                           :<|> Named
                                                  '("put", FileSharingConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary "Put config for fileSharing"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("fileSharing"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        FileSharingConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           FileSharingConfig)))))))))))))))
                                          :<|> (Named
                                                  '("get", ClassifiedDomainsConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Get config for classifiedDomains"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("classifiedDomains"
                                                                                       :> Get
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               ClassifiedDomainsConfig)))))))))))
                                                :<|> ((Named
                                                         '("get", ConferenceCallingConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for conferenceCalling"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("conferenceCalling"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      ConferenceCallingConfig)))))))))))
                                                       :<|> Named
                                                              '("put", ConferenceCallingConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for conferenceCalling"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("conferenceCalling"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    ConferenceCallingConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       ConferenceCallingConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get", SelfDeletingMessagesConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for selfDeletingMessages"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("selfDeletingMessages"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            SelfDeletingMessagesConfig)))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      SelfDeletingMessagesConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for selfDeletingMessages"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("selfDeletingMessages"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          SelfDeletingMessagesConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             SelfDeletingMessagesConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get", GuestLinksConfig)
                                                                     (Description ""
                                                                      :> (ZUser
                                                                          :> (Summary
                                                                                "Get config for conversationGuestLinks"
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("conversationGuestLinks"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  GuestLinksConfig)))))))))))
                                                                   :<|> Named
                                                                          '("put", GuestLinksConfig)
                                                                          (Description ""
                                                                           :> (ZUser
                                                                               :> (Summary
                                                                                     "Put config for conversationGuestLinks"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                GuestLinksConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   GuestLinksConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             SndFactorPasswordChallengeConfig)
                                                                           (Description ""
                                                                            :> (ZUser
                                                                                :> (Summary
                                                                                      "Get config for sndFactorPasswordChallenge"
                                                                                    :> (CanThrow
                                                                                          OperationDenied
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("sndFactorPasswordChallenge"
                                                                                                                :> Get
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        SndFactorPasswordChallengeConfig)))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  SndFactorPasswordChallengeConfig)
                                                                                (Description ""
                                                                                 :> (ZUser
                                                                                     :> (Summary
                                                                                           "Put config for sndFactorPasswordChallenge"
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (Feature
                                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                                 :> Put
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         SndFactorPasswordChallengeConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get", MLSConfig)
                                                                                 (From 'V5
                                                                                  :> (Description ""
                                                                                      :> (ZUser
                                                                                          :> (Summary
                                                                                                "Get config for mls"
                                                                                              :> (CanThrow
                                                                                                    OperationDenied
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mls"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  MLSConfig))))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        MLSConfig)
                                                                                      (From 'V5
                                                                                       :> (Description
                                                                                             ""
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Put config for mls"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("mls"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (Feature
                                                                                                                                                MLSConfig)
                                                                                                                                           :> Put
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   MLSConfig))))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("get",
                                                                                         ExposeInvitationURLsToTeamAdminConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (ZUser
                                                                                            :> (Summary
                                                                                                  "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                                :> (CanThrow
                                                                                                      OperationDenied
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                            :> Get
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                                                     :<|> Named
                                                                                            '("put",
                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (ZUser
                                                                                                 :> (Summary
                                                                                                       "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       TeamFeatureError
                                                                                                                     :> (CanThrowMany
                                                                                                                           '[]
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               (Feature
                                                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                             :> Put
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("get",
                                                                                               SearchVisibilityInboundConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (ZUser
                                                                                                  :> (Summary
                                                                                                        "Get config for searchVisibilityInbound"
                                                                                                      :> (CanThrow
                                                                                                            OperationDenied
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("searchVisibilityInbound"
                                                                                                                                  :> Get
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          SearchVisibilityInboundConfig)))))))))))
                                                                                           :<|> Named
                                                                                                  '("put",
                                                                                                    SearchVisibilityInboundConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (ZUser
                                                                                                       :> (Summary
                                                                                                             "Put config for searchVisibilityInbound"
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             TeamFeatureError
                                                                                                                           :> (CanThrowMany
                                                                                                                                 '[]
                                                                                                                               :> ("teams"
                                                                                                                                   :> (Capture
                                                                                                                                         "tid"
                                                                                                                                         TeamId
                                                                                                                                       :> ("features"
                                                                                                                                           :> ("searchVisibilityInbound"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     (Feature
                                                                                                                                                        SearchVisibilityInboundConfig)
                                                                                                                                                   :> Put
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           SearchVisibilityInboundConfig)))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("get",
                                                                                                     OutlookCalIntegrationConfig)
                                                                                                   (Description
                                                                                                      ""
                                                                                                    :> (ZUser
                                                                                                        :> (Summary
                                                                                                              "Get config for outlookCalIntegration"
                                                                                                            :> (CanThrow
                                                                                                                  OperationDenied
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          'TeamNotFound
                                                                                                                        :> ("teams"
                                                                                                                            :> (Capture
                                                                                                                                  "tid"
                                                                                                                                  TeamId
                                                                                                                                :> ("features"
                                                                                                                                    :> ("outlookCalIntegration"
                                                                                                                                        :> Get
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeature
                                                                                                                                                OutlookCalIntegrationConfig)))))))))))
                                                                                                 :<|> Named
                                                                                                        '("put",
                                                                                                          OutlookCalIntegrationConfig)
                                                                                                        (Description
                                                                                                           ""
                                                                                                         :> (ZUser
                                                                                                             :> (Summary
                                                                                                                   "Put config for outlookCalIntegration"
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               'TeamNotFound
                                                                                                                             :> (CanThrow
                                                                                                                                   TeamFeatureError
                                                                                                                                 :> (CanThrowMany
                                                                                                                                       '[]
                                                                                                                                     :> ("teams"
                                                                                                                                         :> (Capture
                                                                                                                                               "tid"
                                                                                                                                               TeamId
                                                                                                                                             :> ("features"
                                                                                                                                                 :> ("outlookCalIntegration"
                                                                                                                                                     :> (ReqBody
                                                                                                                                                           '[JSON]
                                                                                                                                                           (Feature
                                                                                                                                                              OutlookCalIntegrationConfig)
                                                                                                                                                         :> Put
                                                                                                                                                              '[JSON]
                                                                                                                                                              (LockableFeature
                                                                                                                                                                 OutlookCalIntegrationConfig)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get",
                                                                                                          MlsE2EIdConfig)
                                                                                                        (From
                                                                                                           'V5
                                                                                                         :> (Description
                                                                                                               ""
                                                                                                             :> (ZUser
                                                                                                                 :> (Summary
                                                                                                                       "Get config for mlsE2EId"
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("mlsE2EId"
                                                                                                                                                 :> Get
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MlsE2EIdConfig))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "put-MlsE2EIdConfig@v5"
                                                                                                              (From
                                                                                                                 'V5
                                                                                                               :> (Until
                                                                                                                     'V6
                                                                                                                   :> (ZUser
                                                                                                                       :> (Summary
                                                                                                                             "Put config for mlsE2EId"
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("mlsE2EId"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (Feature
                                                                                                                                                                        MlsE2EIdConfig)
                                                                                                                                                                   :> Put
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("put",
                                                                                                                      MlsE2EIdConfig)
                                                                                                                    (From
                                                                                                                       'V6
                                                                                                                     :> (Description
                                                                                                                           ""
                                                                                                                         :> (ZUser
                                                                                                                             :> (Summary
                                                                                                                                   "Put config for mlsE2EId"
                                                                                                                                 :> (CanThrow
                                                                                                                                       OperationDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("mlsE2EId"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (Feature
                                                                                                                                                                              MlsE2EIdConfig)
                                                                                                                                                                         :> Put
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 MlsE2EIdConfig)))))))))))))))
                                                                                                                  :<|> ((Named
                                                                                                                           '("get",
                                                                                                                             MlsMigrationConfig)
                                                                                                                           (From
                                                                                                                              'V5
                                                                                                                            :> (Description
                                                                                                                                  ""
                                                                                                                                :> (ZUser
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for mlsMigration"
                                                                                                                                        :> (CanThrow
                                                                                                                                              OperationDenied
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("mlsMigration"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            MlsMigrationConfig))))))))))))
                                                                                                                         :<|> Named
                                                                                                                                '("put",
                                                                                                                                  MlsMigrationConfig)
                                                                                                                                (From
                                                                                                                                   'V5
                                                                                                                                 :> (Description
                                                                                                                                       ""
                                                                                                                                     :> (ZUser
                                                                                                                                         :> (Summary
                                                                                                                                               "Put config for mlsMigration"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   OperationDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("mlsMigration"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (Feature
                                                                                                                                                                                          MlsMigrationConfig)
                                                                                                                                                                                     :> Put
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             MlsMigrationConfig))))))))))))))))
                                                                                                                        :<|> ((Named
                                                                                                                                 '("get",
                                                                                                                                   EnforceFileDownloadLocationConfig)
                                                                                                                                 (From
                                                                                                                                    'V5
                                                                                                                                  :> (Description
                                                                                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                      :> (ZUser
                                                                                                                                          :> (Summary
                                                                                                                                                "Get config for enforceFileDownloadLocation"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    OperationDenied
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  EnforceFileDownloadLocationConfig))))))))))))
                                                                                                                               :<|> Named
                                                                                                                                      '("put",
                                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                                      (From
                                                                                                                                         'V5
                                                                                                                                       :> (Description
                                                                                                                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                           :> (ZUser
                                                                                                                                               :> (Summary
                                                                                                                                                     "Put config for enforceFileDownloadLocation"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         OperationDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     TeamFeatureError
                                                                                                                                                                   :> (CanThrowMany
                                                                                                                                                                         '[]
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> ("enforceFileDownloadLocation"
                                                                                                                                                                                       :> (ReqBody
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (Feature
                                                                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                                                                           :> Put
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get",
                                                                                                                                        LimitedEventFanoutConfig)
                                                                                                                                      (From
                                                                                                                                         'V5
                                                                                                                                       :> (Description
                                                                                                                                             ""
                                                                                                                                           :> (ZUser
                                                                                                                                               :> (Summary
                                                                                                                                                     "Get config for limitedEventFanout"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         OperationDenied
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("teams"
                                                                                                                                                                   :> (Capture
                                                                                                                                                                         "tid"
                                                                                                                                                                         TeamId
                                                                                                                                                                       :> ("features"
                                                                                                                                                                           :> ("limitedEventFanout"
                                                                                                                                                                               :> Get
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       LimitedEventFanoutConfig))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-all-feature-configs-for-user"
                                                                                                                                            (Summary
                                                                                                                                               "Gets feature configs for a user"
                                                                                                                                             :> (Description
                                                                                                                                                   "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                                                 :> (DescriptionOAuthScope
                                                                                                                                                       'ReadFeatureConfigs
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> Get
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              AllTeamFeatures))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  "get-all-feature-configs-for-team"
                                                                                                                                                  (Summary
                                                                                                                                                     "Gets feature configs for a team"
                                                                                                                                                   :> (Description
                                                                                                                                                         "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             'NotATeamMember
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 OperationDenied
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                   :> (ZLocalUser
                                                                                                                                                                       :> ("teams"
                                                                                                                                                                           :> (Capture
                                                                                                                                                                                 "tid"
                                                                                                                                                                                 TeamId
                                                                                                                                                                               :> ("features"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        AllTeamFeatures)))))))))
                                                                                                                                                :<|> ((Named
                                                                                                                                                         '("get-deprecated",
                                                                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                                                                         (ZUser
                                                                                                                                                          :> (Summary
                                                                                                                                                                "[deprecated] Get config for searchVisibility"
                                                                                                                                                              :> (Until
                                                                                                                                                                    'V2
                                                                                                                                                                  :> (Description
                                                                                                                                                                        "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                OperationDenied
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                            "tid"
                                                                                                                                                                                            TeamId
                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                              :> ("search-visibility"
                                                                                                                                                                                                  :> Get
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          SearchVisibilityAvailableConfig))))))))))))
                                                                                                                                                       :<|> (Named
                                                                                                                                                               '("put-deprecated",
                                                                                                                                                                 SearchVisibilityAvailableConfig)
                                                                                                                                                               (ZUser
                                                                                                                                                                :> (Summary
                                                                                                                                                                      "[deprecated] Get config for searchVisibility"
                                                                                                                                                                    :> (Until
                                                                                                                                                                          'V2
                                                                                                                                                                        :> (Description
                                                                                                                                                                              "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              TeamFeatureError
                                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                                :> (Capture
                                                                                                                                                                                                      "tid"
                                                                                                                                                                                                      TeamId
                                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                                        :> ("search-visibility"
                                                                                                                                                                                                            :> (ReqBody
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (Feature
                                                                                                                                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                                                                                                                                :> Put
                                                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                                                        SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                                                             :<|> (Named
                                                                                                                                                                     '("get-deprecated",
                                                                                                                                                                       ValidateSAMLEmailsConfig)
                                                                                                                                                                     (ZUser
                                                                                                                                                                      :> (Summary
                                                                                                                                                                            "[deprecated] Get config for validateSAMLemails"
                                                                                                                                                                          :> (Until
                                                                                                                                                                                'V2
                                                                                                                                                                              :> (Description
                                                                                                                                                                                    "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                              :> ("teams"
                                                                                                                                                                                                  :> (Capture
                                                                                                                                                                                                        "tid"
                                                                                                                                                                                                        TeamId
                                                                                                                                                                                                      :> ("features"
                                                                                                                                                                                                          :> ("validate-saml-emails"
                                                                                                                                                                                                              :> Get
                                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                                      ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                                                   :<|> Named
                                                                                                                                                                          '("get-deprecated",
                                                                                                                                                                            DigitalSignaturesConfig)
                                                                                                                                                                          (ZUser
                                                                                                                                                                           :> (Summary
                                                                                                                                                                                 "[deprecated] Get config for digitalSignatures"
                                                                                                                                                                               :> (Until
                                                                                                                                                                                     'V2
                                                                                                                                                                                   :> (Description
                                                                                                                                                                                         "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("teams"
                                                                                                                                                                                                       :> (Capture
                                                                                                                                                                                                             "tid"
                                                                                                                                                                                                             TeamId
                                                                                                                                                                                                           :> ("features"
                                                                                                                                                                                                               :> ("digital-signatures"
                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                           DigitalSignaturesConfig)))))))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                LegalholdConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature legalhold"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("legalhold"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       LegalholdConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      SSOConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature sso"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("sso"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             SSOConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            SearchVisibilityAvailableConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("searchVisibility"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   SearchVisibilityAvailableConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  ValidateSAMLEmailsConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("validateSAMLemails"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        DigitalSignaturesConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("digitalSignatures"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               DigitalSignaturesConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              AppLockConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature appLock"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("appLock"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     AppLockConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    FileSharingConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("fileSharing"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           FileSharingConfig))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        '("get-config",
                                                                                                                                                                                                          ClassifiedDomainsConfig)
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                                                                     :> ("classifiedDomains"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                 ClassifiedDomainsConfig))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              '("get-config",
                                                                                                                                                                                                                ConferenceCallingConfig)
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                                                                           :> ("conferenceCalling"
                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                                       ConferenceCallingConfig))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    '("get-config",
                                                                                                                                                                                                                      SelfDeletingMessagesConfig)
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                                                                 :> ("selfDeletingMessages"
                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                                             SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          '("get-config",
                                                                                                                                                                                                                            GuestLinksConfig)
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                                                                   GuestLinksConfig))))))))))
                                                                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                                                                '("get-config",
                                                                                                                                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                                                (Summary
                                                                                                                                                                                                                                   "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                                                 :> (Until
                                                                                                                                                                                                                                       'V2
                                                                                                                                                                                                                                     :> (Description
                                                                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                                                                         SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                                              :<|> Named
                                                                                                                                                                                                                                     '("get-config",
                                                                                                                                                                                                                                       MLSConfig)
                                                                                                                                                                                                                                     (Summary
                                                                                                                                                                                                                                        "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                                                      :> (Until
                                                                                                                                                                                                                                            'V2
                                                                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                                                                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                              :> (ZUser
                                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                                                                              :> ("feature-configs"
                                                                                                                                                                                                                                                                  :> ("mls"
                                                                                                                                                                                                                                                                      :> Get
                                                                                                                                                                                                                                                                           '[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 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-search-visibility" ServerT
  (Summary "Shows the value for search visibility"
   :> (CanThrow 'NotATeamMember
       :> (CanThrow OperationDenied
           :> (ZLocalUser
               :> ("teams"
                   :> (Capture "tid" TeamId
                       :> ("search-visibility"
                           :> Get '[JSON] TeamSearchVisibilityView)))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Shows the value for search visibility"
            :> (CanThrow 'NotATeamMember
                :> (CanThrow OperationDenied
                    :> (ZLocalUser
                        :> ("teams"
                            :> (Capture "tid" TeamId
                                :> ("search-visibility"
                                    :> 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]))
Local UserId
-> TeamId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member SearchVisibilityStore r, Member TeamStore r) =>
Local UserId -> TeamId -> Sem r TeamSearchVisibilityView
getSearchVisibility
    API
  (Named
     "get-search-visibility"
     (Summary "Shows the value for search visibility"
      :> (CanThrow 'NotATeamMember
          :> (CanThrow OperationDenied
              :> (ZLocalUser
                  :> ("teams"
                      :> (Capture "tid" TeamId
                          :> ("search-visibility"
                              :> 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"
        (Summary "Sets the search visibility for the whole team"
         :> (CanThrow 'NotATeamMember
             :> (CanThrow OperationDenied
                 :> (CanThrow 'TeamSearchVisibilityNotEnabled
                     :> (CanThrow 'TeamNotFound
                         :> (CanThrow TeamFeatureError
                             :> (ZLocalUser
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("search-visibility"
                                             :> (ReqBody '[JSON] TeamSearchVisibilityView
                                                 :> MultiVerb
                                                      'PUT
                                                      '[JSON]
                                                      '[RespondEmpty 204 "Search visibility set"]
                                                      ())))))))))))
      :<|> (Named
              '("get", ValidateSAMLEmailsConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Get config for validateSAMLemails"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> ("teams"
                                       :> (Capture "tid" TeamId
                                           :> ("features"
                                               :> ("validateSAMLemails"
                                                   :> Get
                                                        '[JSON]
                                                        (LockableFeature
                                                           ValidateSAMLEmailsConfig)))))))))))
            :<|> (Named
                    '("get", DigitalSignaturesConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Get config for digitalSignatures"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("digitalSignatures"
                                                         :> Get
                                                              '[JSON]
                                                              (LockableFeature
                                                                 DigitalSignaturesConfig)))))))))))
                  :<|> ((Named
                           '("get", AppLockConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for appLock"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("appLock"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        AppLockConfig)))))))))))
                         :<|> Named
                                '("put", AppLockConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for appLock"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("appLock"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      AppLockConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         AppLockConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", FileSharingConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for fileSharing"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("fileSharing"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              FileSharingConfig)))))))))))
                               :<|> Named
                                      '("put", FileSharingConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for fileSharing"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("fileSharing"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            FileSharingConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               FileSharingConfig)))))))))))))))
                              :<|> (Named
                                      '("get", ClassifiedDomainsConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Get config for classifiedDomains"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("classifiedDomains"
                                                                           :> Get
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   ClassifiedDomainsConfig)))))))))))
                                    :<|> ((Named
                                             '("get", ConferenceCallingConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary "Get config for conferenceCalling"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("conferenceCalling"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          ConferenceCallingConfig)))))))))))
                                           :<|> Named
                                                  '("put", ConferenceCallingConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for conferenceCalling"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("conferenceCalling"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        ConferenceCallingConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           ConferenceCallingConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", SelfDeletingMessagesConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for selfDeletingMessages"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("selfDeletingMessages"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                SelfDeletingMessagesConfig)))))))))))
                                                 :<|> Named
                                                        '("put", SelfDeletingMessagesConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for selfDeletingMessages"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("selfDeletingMessages"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              SelfDeletingMessagesConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 SelfDeletingMessagesConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", GuestLinksConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for conversationGuestLinks"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("conversationGuestLinks"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      GuestLinksConfig)))))))))))
                                                       :<|> Named
                                                              '("put", GuestLinksConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for conversationGuestLinks"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("conversationGuestLinks"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    GuestLinksConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       GuestLinksConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get",
                                                                 SndFactorPasswordChallengeConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for sndFactorPasswordChallenge"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("sndFactorPasswordChallenge"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            SndFactorPasswordChallengeConfig)))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      SndFactorPasswordChallengeConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for sndFactorPasswordChallenge"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             SndFactorPasswordChallengeConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get", MLSConfig)
                                                                     (From 'V5
                                                                      :> (Description ""
                                                                          :> (ZUser
                                                                              :> (Summary
                                                                                    "Get config for mls"
                                                                                  :> (CanThrow
                                                                                        OperationDenied
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mls"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      MLSConfig))))))))))))
                                                                   :<|> Named
                                                                          '("put", MLSConfig)
                                                                          (From 'V5
                                                                           :> (Description ""
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Put config for mls"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("mls"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (Feature
                                                                                                                                    MLSConfig)
                                                                                                                               :> Put
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       MLSConfig))))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                           (Description ""
                                                                            :> (ZUser
                                                                                :> (Summary
                                                                                      "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                    :> (CanThrow
                                                                                          OperationDenied
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                :> Get
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                (Description ""
                                                                                 :> (ZUser
                                                                                     :> (Summary
                                                                                           "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (Feature
                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                 :> Put
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get",
                                                                                   SearchVisibilityInboundConfig)
                                                                                 (Description ""
                                                                                  :> (ZUser
                                                                                      :> (Summary
                                                                                            "Get config for searchVisibilityInbound"
                                                                                          :> (CanThrow
                                                                                                OperationDenied
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("searchVisibilityInbound"
                                                                                                                      :> Get
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              SearchVisibilityInboundConfig)))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        SearchVisibilityInboundConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (ZUser
                                                                                           :> (Summary
                                                                                                 "Put config for searchVisibilityInbound"
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 TeamFeatureError
                                                                                                               :> (CanThrowMany
                                                                                                                     '[]
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("searchVisibilityInbound"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         (Feature
                                                                                                                                            SearchVisibilityInboundConfig)
                                                                                                                                       :> Put
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               SearchVisibilityInboundConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("get",
                                                                                         OutlookCalIntegrationConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (ZUser
                                                                                            :> (Summary
                                                                                                  "Get config for outlookCalIntegration"
                                                                                                :> (CanThrow
                                                                                                      OperationDenied
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("outlookCalIntegration"
                                                                                                                            :> Get
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    OutlookCalIntegrationConfig)))))))))))
                                                                                     :<|> Named
                                                                                            '("put",
                                                                                              OutlookCalIntegrationConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (ZUser
                                                                                                 :> (Summary
                                                                                                       "Put config for outlookCalIntegration"
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       TeamFeatureError
                                                                                                                     :> (CanThrowMany
                                                                                                                           '[]
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("outlookCalIntegration"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               (Feature
                                                                                                                                                  OutlookCalIntegrationConfig)
                                                                                                                                             :> Put
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     OutlookCalIntegrationConfig)))))))))))))))
                                                                                    :<|> (Named
                                                                                            '("get",
                                                                                              MlsE2EIdConfig)
                                                                                            (From
                                                                                               'V5
                                                                                             :> (Description
                                                                                                   ""
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Get config for mlsE2EId"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("mlsE2EId"
                                                                                                                                     :> Get
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             MlsE2EIdConfig))))))))))))
                                                                                          :<|> (Named
                                                                                                  "put-MlsE2EIdConfig@v5"
                                                                                                  (From
                                                                                                     'V5
                                                                                                   :> (Until
                                                                                                         'V6
                                                                                                       :> (ZUser
                                                                                                           :> (Summary
                                                                                                                 "Put config for mlsE2EId"
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("mlsE2EId"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (Feature
                                                                                                                                                            MlsE2EIdConfig)
                                                                                                                                                       :> Put
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               MlsE2EIdConfig)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        '("put",
                                                                                                          MlsE2EIdConfig)
                                                                                                        (From
                                                                                                           'V6
                                                                                                         :> (Description
                                                                                                               ""
                                                                                                             :> (ZUser
                                                                                                                 :> (Summary
                                                                                                                       "Put config for mlsE2EId"
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("mlsE2EId"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (Feature
                                                                                                                                                                  MlsE2EIdConfig)
                                                                                                                                                             :> Put
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     MlsE2EIdConfig)))))))))))))))
                                                                                                      :<|> ((Named
                                                                                                               '("get",
                                                                                                                 MlsMigrationConfig)
                                                                                                               (From
                                                                                                                  'V5
                                                                                                                :> (Description
                                                                                                                      ""
                                                                                                                    :> (ZUser
                                                                                                                        :> (Summary
                                                                                                                              "Get config for mlsMigration"
                                                                                                                            :> (CanThrow
                                                                                                                                  OperationDenied
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("mlsMigration"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                MlsMigrationConfig))))))))))))
                                                                                                             :<|> Named
                                                                                                                    '("put",
                                                                                                                      MlsMigrationConfig)
                                                                                                                    (From
                                                                                                                       'V5
                                                                                                                     :> (Description
                                                                                                                           ""
                                                                                                                         :> (ZUser
                                                                                                                             :> (Summary
                                                                                                                                   "Put config for mlsMigration"
                                                                                                                                 :> (CanThrow
                                                                                                                                       OperationDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("mlsMigration"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (Feature
                                                                                                                                                                              MlsMigrationConfig)
                                                                                                                                                                         :> Put
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 MlsMigrationConfig))))))))))))))))
                                                                                                            :<|> ((Named
                                                                                                                     '("get",
                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                     (From
                                                                                                                        'V5
                                                                                                                      :> (Description
                                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                          :> (ZUser
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for enforceFileDownloadLocation"
                                                                                                                                  :> (CanThrow
                                                                                                                                        OperationDenied
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      EnforceFileDownloadLocationConfig))))))))))))
                                                                                                                   :<|> Named
                                                                                                                          '("put",
                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                          (From
                                                                                                                             'V5
                                                                                                                           :> (Description
                                                                                                                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                               :> (ZUser
                                                                                                                                   :> (Summary
                                                                                                                                         "Put config for enforceFileDownloadLocation"
                                                                                                                                       :> (CanThrow
                                                                                                                                             OperationDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("enforceFileDownloadLocation"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (Feature
                                                                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                                                                               :> Put
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get",
                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                          (From
                                                                                                                             'V5
                                                                                                                           :> (Description
                                                                                                                                 ""
                                                                                                                               :> (ZUser
                                                                                                                                   :> (Summary
                                                                                                                                         "Get config for limitedEventFanout"
                                                                                                                                       :> (CanThrow
                                                                                                                                             OperationDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("teams"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "tid"
                                                                                                                                                             TeamId
                                                                                                                                                           :> ("features"
                                                                                                                                                               :> ("limitedEventFanout"
                                                                                                                                                                   :> Get
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           LimitedEventFanoutConfig))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-all-feature-configs-for-user"
                                                                                                                                (Summary
                                                                                                                                   "Gets feature configs for a user"
                                                                                                                                 :> (Description
                                                                                                                                       "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                           'ReadFeatureConfigs
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> Get
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  AllTeamFeatures))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-all-feature-configs-for-team"
                                                                                                                                      (Summary
                                                                                                                                         "Gets feature configs for a team"
                                                                                                                                       :> (Description
                                                                                                                                             "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     OperationDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'TeamNotFound
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            AllTeamFeatures)))))))))
                                                                                                                                    :<|> ((Named
                                                                                                                                             '("get-deprecated",
                                                                                                                                               SearchVisibilityAvailableConfig)
                                                                                                                                             (ZUser
                                                                                                                                              :> (Summary
                                                                                                                                                    "[deprecated] Get config for searchVisibility"
                                                                                                                                                  :> (Until
                                                                                                                                                        'V2
                                                                                                                                                      :> (Description
                                                                                                                                                            "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'NotATeamMember
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    OperationDenied
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("search-visibility"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              SearchVisibilityAvailableConfig))))))))))))
                                                                                                                                           :<|> (Named
                                                                                                                                                   '("put-deprecated",
                                                                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                                                                   (ZUser
                                                                                                                                                    :> (Summary
                                                                                                                                                          "[deprecated] Get config for searchVisibility"
                                                                                                                                                        :> (Until
                                                                                                                                                              'V2
                                                                                                                                                            :> (Description
                                                                                                                                                                  "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          OperationDenied
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                :> ("teams"
                                                                                                                                                                                    :> (Capture
                                                                                                                                                                                          "tid"
                                                                                                                                                                                          TeamId
                                                                                                                                                                                        :> ("features"
                                                                                                                                                                                            :> ("search-visibility"
                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (Feature
                                                                                                                                                                                                         SearchVisibilityAvailableConfig)
                                                                                                                                                                                                    :> Put
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                                            SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                                                 :<|> (Named
                                                                                                                                                         '("get-deprecated",
                                                                                                                                                           ValidateSAMLEmailsConfig)
                                                                                                                                                         (ZUser
                                                                                                                                                          :> (Summary
                                                                                                                                                                "[deprecated] Get config for validateSAMLemails"
                                                                                                                                                              :> (Until
                                                                                                                                                                    'V2
                                                                                                                                                                  :> (Description
                                                                                                                                                                        "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                OperationDenied
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                            "tid"
                                                                                                                                                                                            TeamId
                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                              :> ("validate-saml-emails"
                                                                                                                                                                                                  :> Get
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                                       :<|> Named
                                                                                                                                                              '("get-deprecated",
                                                                                                                                                                DigitalSignaturesConfig)
                                                                                                                                                              (ZUser
                                                                                                                                                               :> (Summary
                                                                                                                                                                     "[deprecated] Get config for digitalSignatures"
                                                                                                                                                                   :> (Until
                                                                                                                                                                         'V2
                                                                                                                                                                       :> (Description
                                                                                                                                                                             "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("teams"
                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                 "tid"
                                                                                                                                                                                                 TeamId
                                                                                                                                                                                               :> ("features"
                                                                                                                                                                                                   :> ("digital-signatures"
                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               DigitalSignaturesConfig)))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    LegalholdConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature legalhold"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("legalhold"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           LegalholdConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          SSOConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature sso"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("sso"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 SSOConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                SearchVisibilityAvailableConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("searchVisibility"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       SearchVisibilityAvailableConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      ValidateSAMLEmailsConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("validateSAMLemails"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            DigitalSignaturesConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("digitalSignatures"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   DigitalSignaturesConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  AppLockConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature appLock"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("appLock"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         AppLockConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        FileSharingConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("fileSharing"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               FileSharingConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              ClassifiedDomainsConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("classifiedDomains"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     ClassifiedDomainsConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    ConferenceCallingConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("conferenceCalling"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           ConferenceCallingConfig))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        '("get-config",
                                                                                                                                                                                                          SelfDeletingMessagesConfig)
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                                                                     :> ("selfDeletingMessages"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                 SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              '("get-config",
                                                                                                                                                                                                                GuestLinksConfig)
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                                       GuestLinksConfig))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    '("get-config",
                                                                                                                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                                             SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                                  :<|> Named
                                                                                                                                                                                                                         '("get-config",
                                                                                                                                                                                                                           MLSConfig)
                                                                                                                                                                                                                         (Summary
                                                                                                                                                                                                                            "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                                          :> (Until
                                                                                                                                                                                                                                'V2
                                                                                                                                                                                                                              :> (Description
                                                                                                                                                                                                                                    "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                  :> (ZUser
                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                                                                  :> ("feature-configs"
                                                                                                                                                                                                                                                      :> ("mls"
                                                                                                                                                                                                                                                          :> Get
                                                                                                                                                                                                                                                               '[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
        "get-search-visibility"
        (Summary "Shows the value for search visibility"
         :> (CanThrow 'NotATeamMember
             :> (CanThrow OperationDenied
                 :> (ZLocalUser
                     :> ("teams"
                         :> (Capture "tid" TeamId
                             :> ("search-visibility"
                                 :> Get '[JSON] TeamSearchVisibilityView)))))))
      :<|> (Named
              "set-search-visibility"
              (Summary "Sets the search visibility for the whole team"
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamSearchVisibilityNotEnabled
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (ZLocalUser
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("search-visibility"
                                                   :> (ReqBody '[JSON] TeamSearchVisibilityView
                                                       :> MultiVerb
                                                            'PUT
                                                            '[JSON]
                                                            '[RespondEmpty
                                                                204 "Search visibility set"]
                                                            ())))))))))))
            :<|> (Named
                    '("get", ValidateSAMLEmailsConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Get config for validateSAMLemails"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("validateSAMLemails"
                                                         :> Get
                                                              '[JSON]
                                                              (LockableFeature
                                                                 ValidateSAMLEmailsConfig)))))))))))
                  :<|> (Named
                          '("get", DigitalSignaturesConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Get config for digitalSignatures"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("digitalSignatures"
                                                               :> Get
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       DigitalSignaturesConfig)))))))))))
                        :<|> ((Named
                                 '("get", AppLockConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for appLock"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("appLock"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              AppLockConfig)))))))))))
                               :<|> Named
                                      '("put", AppLockConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for appLock"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("appLock"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            AppLockConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               AppLockConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", FileSharingConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for fileSharing"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("fileSharing"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    FileSharingConfig)))))))))))
                                     :<|> Named
                                            '("put", FileSharingConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Put config for fileSharing"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("fileSharing"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  FileSharingConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     FileSharingConfig)))))))))))))))
                                    :<|> (Named
                                            '("get", ClassifiedDomainsConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Get config for classifiedDomains"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("classifiedDomains"
                                                                                 :> Get
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         ClassifiedDomainsConfig)))))))))))
                                          :<|> ((Named
                                                   '("get", ConferenceCallingConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for conferenceCalling"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("conferenceCalling"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                ConferenceCallingConfig)))))))))))
                                                 :<|> Named
                                                        '("put", ConferenceCallingConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for conferenceCalling"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("conferenceCalling"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              ConferenceCallingConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 ConferenceCallingConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", SelfDeletingMessagesConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for selfDeletingMessages"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("selfDeletingMessages"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      SelfDeletingMessagesConfig)))))))))))
                                                       :<|> Named
                                                              '("put", SelfDeletingMessagesConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for selfDeletingMessages"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("selfDeletingMessages"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    SelfDeletingMessagesConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       SelfDeletingMessagesConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get", GuestLinksConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for conversationGuestLinks"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("conversationGuestLinks"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            GuestLinksConfig)))))))))))
                                                             :<|> Named
                                                                    '("put", GuestLinksConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for conversationGuestLinks"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("conversationGuestLinks"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          GuestLinksConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             GuestLinksConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get",
                                                                       SndFactorPasswordChallengeConfig)
                                                                     (Description ""
                                                                      :> (ZUser
                                                                          :> (Summary
                                                                                "Get config for sndFactorPasswordChallenge"
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("sndFactorPasswordChallenge"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  SndFactorPasswordChallengeConfig)))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            SndFactorPasswordChallengeConfig)
                                                                          (Description ""
                                                                           :> (ZUser
                                                                               :> (Summary
                                                                                     "Put config for sndFactorPasswordChallenge"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   SndFactorPasswordChallengeConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get", MLSConfig)
                                                                           (From 'V5
                                                                            :> (Description ""
                                                                                :> (ZUser
                                                                                    :> (Summary
                                                                                          "Get config for mls"
                                                                                        :> (CanThrow
                                                                                              OperationDenied
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mls"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            MLSConfig))))))))))))
                                                                         :<|> Named
                                                                                '("put", MLSConfig)
                                                                                (From 'V5
                                                                                 :> (Description ""
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Put config for mls"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("mls"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (Feature
                                                                                                                                          MLSConfig)
                                                                                                                                     :> Put
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             MLSConfig))))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get",
                                                                                   ExposeInvitationURLsToTeamAdminConfig)
                                                                                 (Description ""
                                                                                  :> (ZUser
                                                                                      :> (Summary
                                                                                            "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                          :> (CanThrow
                                                                                                OperationDenied
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                      :> Get
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (ZUser
                                                                                           :> (Summary
                                                                                                 "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 TeamFeatureError
                                                                                                               :> (CanThrowMany
                                                                                                                     '[]
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         (Feature
                                                                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                       :> Put
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("get",
                                                                                         SearchVisibilityInboundConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (ZUser
                                                                                            :> (Summary
                                                                                                  "Get config for searchVisibilityInbound"
                                                                                                :> (CanThrow
                                                                                                      OperationDenied
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("searchVisibilityInbound"
                                                                                                                            :> Get
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    SearchVisibilityInboundConfig)))))))))))
                                                                                     :<|> Named
                                                                                            '("put",
                                                                                              SearchVisibilityInboundConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (ZUser
                                                                                                 :> (Summary
                                                                                                       "Put config for searchVisibilityInbound"
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       TeamFeatureError
                                                                                                                     :> (CanThrowMany
                                                                                                                           '[]
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("searchVisibilityInbound"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               (Feature
                                                                                                                                                  SearchVisibilityInboundConfig)
                                                                                                                                             :> Put
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     SearchVisibilityInboundConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("get",
                                                                                               OutlookCalIntegrationConfig)
                                                                                             (Description
                                                                                                ""
                                                                                              :> (ZUser
                                                                                                  :> (Summary
                                                                                                        "Get config for outlookCalIntegration"
                                                                                                      :> (CanThrow
                                                                                                            OperationDenied
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    'TeamNotFound
                                                                                                                  :> ("teams"
                                                                                                                      :> (Capture
                                                                                                                            "tid"
                                                                                                                            TeamId
                                                                                                                          :> ("features"
                                                                                                                              :> ("outlookCalIntegration"
                                                                                                                                  :> Get
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          OutlookCalIntegrationConfig)))))))))))
                                                                                           :<|> Named
                                                                                                  '("put",
                                                                                                    OutlookCalIntegrationConfig)
                                                                                                  (Description
                                                                                                     ""
                                                                                                   :> (ZUser
                                                                                                       :> (Summary
                                                                                                             "Put config for outlookCalIntegration"
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         'TeamNotFound
                                                                                                                       :> (CanThrow
                                                                                                                             TeamFeatureError
                                                                                                                           :> (CanThrowMany
                                                                                                                                 '[]
                                                                                                                               :> ("teams"
                                                                                                                                   :> (Capture
                                                                                                                                         "tid"
                                                                                                                                         TeamId
                                                                                                                                       :> ("features"
                                                                                                                                           :> ("outlookCalIntegration"
                                                                                                                                               :> (ReqBody
                                                                                                                                                     '[JSON]
                                                                                                                                                     (Feature
                                                                                                                                                        OutlookCalIntegrationConfig)
                                                                                                                                                   :> Put
                                                                                                                                                        '[JSON]
                                                                                                                                                        (LockableFeature
                                                                                                                                                           OutlookCalIntegrationConfig)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get",
                                                                                                    MlsE2EIdConfig)
                                                                                                  (From
                                                                                                     'V5
                                                                                                   :> (Description
                                                                                                         ""
                                                                                                       :> (ZUser
                                                                                                           :> (Summary
                                                                                                                 "Get config for mlsE2EId"
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("mlsE2EId"
                                                                                                                                           :> Get
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   MlsE2EIdConfig))))))))))))
                                                                                                :<|> (Named
                                                                                                        "put-MlsE2EIdConfig@v5"
                                                                                                        (From
                                                                                                           'V5
                                                                                                         :> (Until
                                                                                                               'V6
                                                                                                             :> (ZUser
                                                                                                                 :> (Summary
                                                                                                                       "Put config for mlsE2EId"
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("mlsE2EId"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (Feature
                                                                                                                                                                  MlsE2EIdConfig)
                                                                                                                                                             :> Put
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     MlsE2EIdConfig)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("put",
                                                                                                                MlsE2EIdConfig)
                                                                                                              (From
                                                                                                                 'V6
                                                                                                               :> (Description
                                                                                                                     ""
                                                                                                                   :> (ZUser
                                                                                                                       :> (Summary
                                                                                                                             "Put config for mlsE2EId"
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("mlsE2EId"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (Feature
                                                                                                                                                                        MlsE2EIdConfig)
                                                                                                                                                                   :> Put
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                                                                            :<|> ((Named
                                                                                                                     '("get",
                                                                                                                       MlsMigrationConfig)
                                                                                                                     (From
                                                                                                                        'V5
                                                                                                                      :> (Description
                                                                                                                            ""
                                                                                                                          :> (ZUser
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for mlsMigration"
                                                                                                                                  :> (CanThrow
                                                                                                                                        OperationDenied
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("mlsMigration"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      MlsMigrationConfig))))))))))))
                                                                                                                   :<|> Named
                                                                                                                          '("put",
                                                                                                                            MlsMigrationConfig)
                                                                                                                          (From
                                                                                                                             'V5
                                                                                                                           :> (Description
                                                                                                                                 ""
                                                                                                                               :> (ZUser
                                                                                                                                   :> (Summary
                                                                                                                                         "Put config for mlsMigration"
                                                                                                                                       :> (CanThrow
                                                                                                                                             OperationDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("mlsMigration"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (Feature
                                                                                                                                                                                    MlsMigrationConfig)
                                                                                                                                                                               :> Put
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       MlsMigrationConfig))))))))))))))))
                                                                                                                  :<|> ((Named
                                                                                                                           '("get",
                                                                                                                             EnforceFileDownloadLocationConfig)
                                                                                                                           (From
                                                                                                                              'V5
                                                                                                                            :> (Description
                                                                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                :> (ZUser
                                                                                                                                    :> (Summary
                                                                                                                                          "Get config for enforceFileDownloadLocation"
                                                                                                                                        :> (CanThrow
                                                                                                                                              OperationDenied
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            EnforceFileDownloadLocationConfig))))))))))))
                                                                                                                         :<|> Named
                                                                                                                                '("put",
                                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                                                (From
                                                                                                                                   'V5
                                                                                                                                 :> (Description
                                                                                                                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                                     :> (ZUser
                                                                                                                                         :> (Summary
                                                                                                                                               "Put config for enforceFileDownloadLocation"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   OperationDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               TeamFeatureError
                                                                                                                                                             :> (CanThrowMany
                                                                                                                                                                   '[]
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                                                                                                 :> (ReqBody
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (Feature
                                                                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                                                                     :> Put
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get",
                                                                                                                                  LimitedEventFanoutConfig)
                                                                                                                                (From
                                                                                                                                   'V5
                                                                                                                                 :> (Description
                                                                                                                                       ""
                                                                                                                                     :> (ZUser
                                                                                                                                         :> (Summary
                                                                                                                                               "Get config for limitedEventFanout"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   OperationDenied
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("teams"
                                                                                                                                                             :> (Capture
                                                                                                                                                                   "tid"
                                                                                                                                                                   TeamId
                                                                                                                                                                 :> ("features"
                                                                                                                                                                     :> ("limitedEventFanout"
                                                                                                                                                                         :> Get
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 LimitedEventFanoutConfig))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-all-feature-configs-for-user"
                                                                                                                                      (Summary
                                                                                                                                         "Gets feature configs for a user"
                                                                                                                                       :> (Description
                                                                                                                                             "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                                           :> (DescriptionOAuthScope
                                                                                                                                                 'ReadFeatureConfigs
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> Get
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        AllTeamFeatures))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            "get-all-feature-configs-for-team"
                                                                                                                                            (Summary
                                                                                                                                               "Gets feature configs for a team"
                                                                                                                                             :> (Description
                                                                                                                                                   "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       'NotATeamMember
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           OperationDenied
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'TeamNotFound
                                                                                                                                                             :> (ZLocalUser
                                                                                                                                                                 :> ("teams"
                                                                                                                                                                     :> (Capture
                                                                                                                                                                           "tid"
                                                                                                                                                                           TeamId
                                                                                                                                                                         :> ("features"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  AllTeamFeatures)))))))))
                                                                                                                                          :<|> ((Named
                                                                                                                                                   '("get-deprecated",
                                                                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                                                                   (ZUser
                                                                                                                                                    :> (Summary
                                                                                                                                                          "[deprecated] Get config for searchVisibility"
                                                                                                                                                        :> (Until
                                                                                                                                                              'V2
                                                                                                                                                            :> (Description
                                                                                                                                                                  "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          OperationDenied
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                :> (Capture
                                                                                                                                                                                      "tid"
                                                                                                                                                                                      TeamId
                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                        :> ("search-visibility"
                                                                                                                                                                                            :> Get
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    SearchVisibilityAvailableConfig))))))))))))
                                                                                                                                                 :<|> (Named
                                                                                                                                                         '("put-deprecated",
                                                                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                                                                         (ZUser
                                                                                                                                                          :> (Summary
                                                                                                                                                                "[deprecated] Get config for searchVisibility"
                                                                                                                                                              :> (Until
                                                                                                                                                                    'V2
                                                                                                                                                                  :> (Description
                                                                                                                                                                        "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                OperationDenied
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        TeamFeatureError
                                                                                                                                                                                      :> ("teams"
                                                                                                                                                                                          :> (Capture
                                                                                                                                                                                                "tid"
                                                                                                                                                                                                TeamId
                                                                                                                                                                                              :> ("features"
                                                                                                                                                                                                  :> ("search-visibility"
                                                                                                                                                                                                      :> (ReqBody
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (Feature
                                                                                                                                                                                                               SearchVisibilityAvailableConfig)
                                                                                                                                                                                                          :> Put
                                                                                                                                                                                                               '[JSON]
                                                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                                                  SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                                                       :<|> (Named
                                                                                                                                                               '("get-deprecated",
                                                                                                                                                                 ValidateSAMLEmailsConfig)
                                                                                                                                                               (ZUser
                                                                                                                                                                :> (Summary
                                                                                                                                                                      "[deprecated] Get config for validateSAMLemails"
                                                                                                                                                                    :> (Until
                                                                                                                                                                          'V2
                                                                                                                                                                        :> (Description
                                                                                                                                                                              "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                        :> ("teams"
                                                                                                                                                                                            :> (Capture
                                                                                                                                                                                                  "tid"
                                                                                                                                                                                                  TeamId
                                                                                                                                                                                                :> ("features"
                                                                                                                                                                                                    :> ("validate-saml-emails"
                                                                                                                                                                                                        :> Get
                                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                                ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                                             :<|> Named
                                                                                                                                                                    '("get-deprecated",
                                                                                                                                                                      DigitalSignaturesConfig)
                                                                                                                                                                    (ZUser
                                                                                                                                                                     :> (Summary
                                                                                                                                                                           "[deprecated] Get config for digitalSignatures"
                                                                                                                                                                         :> (Until
                                                                                                                                                                               'V2
                                                                                                                                                                             :> (Description
                                                                                                                                                                                   "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("teams"
                                                                                                                                                                                                 :> (Capture
                                                                                                                                                                                                       "tid"
                                                                                                                                                                                                       TeamId
                                                                                                                                                                                                     :> ("features"
                                                                                                                                                                                                         :> ("digital-signatures"
                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                     DigitalSignaturesConfig)))))))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          LegalholdConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature legalhold"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("legalhold"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 LegalholdConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                SSOConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature sso"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("sso"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       SSOConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      SearchVisibilityAvailableConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("searchVisibility"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             SearchVisibilityAvailableConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            ValidateSAMLEmailsConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("validateSAMLemails"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  DigitalSignaturesConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("digitalSignatures"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         DigitalSignaturesConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        AppLockConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature appLock"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("appLock"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               AppLockConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              FileSharingConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("fileSharing"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     FileSharingConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    ClassifiedDomainsConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("classifiedDomains"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           ClassifiedDomainsConfig))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        '("get-config",
                                                                                                                                                                                                          ConferenceCallingConfig)
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                                                                     :> ("conferenceCalling"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                 ConferenceCallingConfig))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              '("get-config",
                                                                                                                                                                                                                SelfDeletingMessagesConfig)
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                                                                           :> ("selfDeletingMessages"
                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                                       SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    '("get-config",
                                                                                                                                                                                                                      GuestLinksConfig)
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                                             GuestLinksConfig))))))))))
                                                                                                                                                                                                                  :<|> (Named
                                                                                                                                                                                                                          '("get-config",
                                                                                                                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                                          (Summary
                                                                                                                                                                                                                             "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                                           :> (Until
                                                                                                                                                                                                                                 'V2
                                                                                                                                                                                                                               :> (Description
                                                                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                                                                   SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                                        :<|> Named
                                                                                                                                                                                                                               '("get-config",
                                                                                                                                                                                                                                 MLSConfig)
                                                                                                                                                                                                                               (Summary
                                                                                                                                                                                                                                  "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                                                :> (Until
                                                                                                                                                                                                                                      'V2
                                                                                                                                                                                                                                    :> (Description
                                                                                                                                                                                                                                          "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                        :> (ZUser
                                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                                                                        :> ("feature-configs"
                                                                                                                                                                                                                                                            :> ("mls"
                                                                                                                                                                                                                                                                :> Get
                                                                                                                                                                                                                                                                     '[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 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" ((TeamId
 -> Sem
      '[Error (Tagged 'NotATeamMember ()),
        Error (Tagged OperationDenied ()),
        Error (Tagged 'TeamSearchVisibilityNotEnabled ()),
        Error (Tagged 'TeamNotFound ()), Error TeamFeatureError,
        BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
        Rpc, ExternalAccess, FederatorAccess,
        BackendNotificationQueueAccess, BotAccess, FireAndForget,
        ClientStore, CodeStore, ProposalStore, ConversationStore,
        SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
        LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
        TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (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)
-> Local UserId
-> TeamId
-> TeamSearchVisibilityView
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()),
       Error (Tagged 'TeamSearchVisibilityNotEnabled ()),
       Error (Tagged 'TeamNotFound ()), Error TeamFeatureError,
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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 (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member (Error (Tagged 'TeamSearchVisibilityNotEnabled ())) r,
 Member SearchVisibilityStore r, Member TeamStore r) =>
(TeamId -> Sem r Bool)
-> Local UserId -> TeamId -> TeamSearchVisibilityView -> Sem r ()
setSearchVisibility (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))
    API
  (Named
     "set-search-visibility"
     (Summary "Sets the search visibility for the whole team"
      :> (CanThrow 'NotATeamMember
          :> (CanThrow OperationDenied
              :> (CanThrow 'TeamSearchVisibilityNotEnabled
                  :> (CanThrow 'TeamNotFound
                      :> (CanThrow TeamFeatureError
                          :> (ZLocalUser
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("search-visibility"
                                          :> (ReqBody '[JSON] TeamSearchVisibilityView
                                              :> MultiVerb
                                                   'PUT
                                                   '[JSON]
                                                   '[RespondEmpty 204 "Search visibility set"]
                                                   ()))))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), 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", ValidateSAMLEmailsConfig)
        (Description ""
         :> (ZUser
             :> (Summary "Get config for validateSAMLemails"
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> ("validateSAMLemails"
                                             :> Get
                                                  '[JSON]
                                                  (LockableFeature
                                                     ValidateSAMLEmailsConfig)))))))))))
      :<|> (Named
              '("get", DigitalSignaturesConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Get config for digitalSignatures"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> ("teams"
                                       :> (Capture "tid" TeamId
                                           :> ("features"
                                               :> ("digitalSignatures"
                                                   :> Get
                                                        '[JSON]
                                                        (LockableFeature
                                                           DigitalSignaturesConfig)))))))))))
            :<|> ((Named
                     '("get", AppLockConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for appLock"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("appLock"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  AppLockConfig)))))))))))
                   :<|> Named
                          '("put", AppLockConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for appLock"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("appLock"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature AppLockConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   AppLockConfig)))))))))))))))
                  :<|> ((Named
                           '("get", FileSharingConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for fileSharing"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("fileSharing"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        FileSharingConfig)))))))))))
                         :<|> Named
                                '("put", FileSharingConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for fileSharing"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("fileSharing"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      FileSharingConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         FileSharingConfig)))))))))))))))
                        :<|> (Named
                                '("get", ClassifiedDomainsConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Get config for classifiedDomains"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("classifiedDomains"
                                                                     :> Get
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             ClassifiedDomainsConfig)))))))))))
                              :<|> ((Named
                                       '("get", ConferenceCallingConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for conferenceCalling"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("conferenceCalling"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    ConferenceCallingConfig)))))))))))
                                     :<|> Named
                                            '("put", ConferenceCallingConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Put config for conferenceCalling"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("conferenceCalling"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  ConferenceCallingConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     ConferenceCallingConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", SelfDeletingMessagesConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary "Get config for selfDeletingMessages"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("selfDeletingMessages"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          SelfDeletingMessagesConfig)))))))))))
                                           :<|> Named
                                                  '("put", SelfDeletingMessagesConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for selfDeletingMessages"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("selfDeletingMessages"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        SelfDeletingMessagesConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           SelfDeletingMessagesConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", GuestLinksConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for conversationGuestLinks"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("conversationGuestLinks"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                GuestLinksConfig)))))))))))
                                                 :<|> Named
                                                        '("put", GuestLinksConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for conversationGuestLinks"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("conversationGuestLinks"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              GuestLinksConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 GuestLinksConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", SndFactorPasswordChallengeConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for sndFactorPasswordChallenge"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("sndFactorPasswordChallenge"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      SndFactorPasswordChallengeConfig)))))))))))
                                                       :<|> Named
                                                              '("put",
                                                                SndFactorPasswordChallengeConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for sndFactorPasswordChallenge"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       SndFactorPasswordChallengeConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get", MLSConfig)
                                                               (From 'V5
                                                                :> (Description ""
                                                                    :> (ZUser
                                                                        :> (Summary
                                                                              "Get config for mls"
                                                                            :> (CanThrow
                                                                                  OperationDenied
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mls"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                MLSConfig))))))))))))
                                                             :<|> Named
                                                                    '("put", MLSConfig)
                                                                    (From 'V5
                                                                     :> (Description ""
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Put config for mls"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("mls"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (Feature
                                                                                                                              MLSConfig)
                                                                                                                         :> Put
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 MLSConfig))))))))))))))))
                                                            :<|> ((Named
                                                                     '("get",
                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                     (Description ""
                                                                      :> (ZUser
                                                                          :> (Summary
                                                                                "Get config for exposeInvitationURLsToTeamAdmin"
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                          (Description ""
                                                                           :> (ZUser
                                                                               :> (Summary
                                                                                     "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             SearchVisibilityInboundConfig)
                                                                           (Description ""
                                                                            :> (ZUser
                                                                                :> (Summary
                                                                                      "Get config for searchVisibilityInbound"
                                                                                    :> (CanThrow
                                                                                          OperationDenied
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("searchVisibilityInbound"
                                                                                                                :> Get
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        SearchVisibilityInboundConfig)))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  SearchVisibilityInboundConfig)
                                                                                (Description ""
                                                                                 :> (ZUser
                                                                                     :> (Summary
                                                                                           "Put config for searchVisibilityInbound"
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("searchVisibilityInbound"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (Feature
                                                                                                                                      SearchVisibilityInboundConfig)
                                                                                                                                 :> Put
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         SearchVisibilityInboundConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get",
                                                                                   OutlookCalIntegrationConfig)
                                                                                 (Description ""
                                                                                  :> (ZUser
                                                                                      :> (Summary
                                                                                            "Get config for outlookCalIntegration"
                                                                                          :> (CanThrow
                                                                                                OperationDenied
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("outlookCalIntegration"
                                                                                                                      :> Get
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              OutlookCalIntegrationConfig)))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        OutlookCalIntegrationConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (ZUser
                                                                                           :> (Summary
                                                                                                 "Put config for outlookCalIntegration"
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 TeamFeatureError
                                                                                                               :> (CanThrowMany
                                                                                                                     '[]
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("outlookCalIntegration"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         (Feature
                                                                                                                                            OutlookCalIntegrationConfig)
                                                                                                                                       :> Put
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               OutlookCalIntegrationConfig)))))))))))))))
                                                                              :<|> (Named
                                                                                      '("get",
                                                                                        MlsE2EIdConfig)
                                                                                      (From 'V5
                                                                                       :> (Description
                                                                                             ""
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Get config for mlsE2EId"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("mlsE2EId"
                                                                                                                               :> Get
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       MlsE2EIdConfig))))))))))))
                                                                                    :<|> (Named
                                                                                            "put-MlsE2EIdConfig@v5"
                                                                                            (From
                                                                                               'V5
                                                                                             :> (Until
                                                                                                   'V6
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Put config for mlsE2EId"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("mlsE2EId"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (Feature
                                                                                                                                                      MlsE2EIdConfig)
                                                                                                                                                 :> Put
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MlsE2EIdConfig)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  '("put",
                                                                                                    MlsE2EIdConfig)
                                                                                                  (From
                                                                                                     'V6
                                                                                                   :> (Description
                                                                                                         ""
                                                                                                       :> (ZUser
                                                                                                           :> (Summary
                                                                                                                 "Put config for mlsE2EId"
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("mlsE2EId"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (Feature
                                                                                                                                                            MlsE2EIdConfig)
                                                                                                                                                       :> Put
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               MlsE2EIdConfig)))))))))))))))
                                                                                                :<|> ((Named
                                                                                                         '("get",
                                                                                                           MlsMigrationConfig)
                                                                                                         (From
                                                                                                            'V5
                                                                                                          :> (Description
                                                                                                                ""
                                                                                                              :> (ZUser
                                                                                                                  :> (Summary
                                                                                                                        "Get config for mlsMigration"
                                                                                                                      :> (CanThrow
                                                                                                                            OperationDenied
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("mlsMigration"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          MlsMigrationConfig))))))))))))
                                                                                                       :<|> Named
                                                                                                              '("put",
                                                                                                                MlsMigrationConfig)
                                                                                                              (From
                                                                                                                 'V5
                                                                                                               :> (Description
                                                                                                                     ""
                                                                                                                   :> (ZUser
                                                                                                                       :> (Summary
                                                                                                                             "Put config for mlsMigration"
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("mlsMigration"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (Feature
                                                                                                                                                                        MlsMigrationConfig)
                                                                                                                                                                   :> Put
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           MlsMigrationConfig))))))))))))))))
                                                                                                      :<|> ((Named
                                                                                                               '("get",
                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                               (From
                                                                                                                  'V5
                                                                                                                :> (Description
                                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                    :> (ZUser
                                                                                                                        :> (Summary
                                                                                                                              "Get config for enforceFileDownloadLocation"
                                                                                                                            :> (CanThrow
                                                                                                                                  OperationDenied
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                EnforceFileDownloadLocationConfig))))))))))))
                                                                                                             :<|> Named
                                                                                                                    '("put",
                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                    (From
                                                                                                                       'V5
                                                                                                                     :> (Description
                                                                                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                         :> (ZUser
                                                                                                                             :> (Summary
                                                                                                                                   "Put config for enforceFileDownloadLocation"
                                                                                                                                 :> (CanThrow
                                                                                                                                       OperationDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("enforceFileDownloadLocation"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (Feature
                                                                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                                                                         :> Put
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get",
                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                    (From
                                                                                                                       'V5
                                                                                                                     :> (Description
                                                                                                                           ""
                                                                                                                         :> (ZUser
                                                                                                                             :> (Summary
                                                                                                                                   "Get config for limitedEventFanout"
                                                                                                                                 :> (CanThrow
                                                                                                                                       OperationDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("limitedEventFanout"
                                                                                                                                                             :> Get
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     LimitedEventFanoutConfig))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-all-feature-configs-for-user"
                                                                                                                          (Summary
                                                                                                                             "Gets feature configs for a user"
                                                                                                                           :> (Description
                                                                                                                                 "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                     'ReadFeatureConfigs
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> Get
                                                                                                                                                            '[JSON]
                                                                                                                                                            AllTeamFeatures))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-all-feature-configs-for-team"
                                                                                                                                (Summary
                                                                                                                                   "Gets feature configs for a team"
                                                                                                                                 :> (Description
                                                                                                                                       "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               OperationDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'TeamNotFound
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      AllTeamFeatures)))))))))
                                                                                                                              :<|> ((Named
                                                                                                                                       '("get-deprecated",
                                                                                                                                         SearchVisibilityAvailableConfig)
                                                                                                                                       (ZUser
                                                                                                                                        :> (Summary
                                                                                                                                              "[deprecated] Get config for searchVisibility"
                                                                                                                                            :> (Until
                                                                                                                                                  'V2
                                                                                                                                                :> (Description
                                                                                                                                                      "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'NotATeamMember
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              OperationDenied
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("search-visibility"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        SearchVisibilityAvailableConfig))))))))))))
                                                                                                                                     :<|> (Named
                                                                                                                                             '("put-deprecated",
                                                                                                                                               SearchVisibilityAvailableConfig)
                                                                                                                                             (ZUser
                                                                                                                                              :> (Summary
                                                                                                                                                    "[deprecated] Get config for searchVisibility"
                                                                                                                                                  :> (Until
                                                                                                                                                        'V2
                                                                                                                                                      :> (Description
                                                                                                                                                            "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'NotATeamMember
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    OperationDenied
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> ("teams"
                                                                                                                                                                              :> (Capture
                                                                                                                                                                                    "tid"
                                                                                                                                                                                    TeamId
                                                                                                                                                                                  :> ("features"
                                                                                                                                                                                      :> ("search-visibility"
                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (Feature
                                                                                                                                                                                                   SearchVisibilityAvailableConfig)
                                                                                                                                                                                              :> Put
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                      SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                                           :<|> (Named
                                                                                                                                                   '("get-deprecated",
                                                                                                                                                     ValidateSAMLEmailsConfig)
                                                                                                                                                   (ZUser
                                                                                                                                                    :> (Summary
                                                                                                                                                          "[deprecated] Get config for validateSAMLemails"
                                                                                                                                                        :> (Until
                                                                                                                                                              'V2
                                                                                                                                                            :> (Description
                                                                                                                                                                  "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          OperationDenied
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                :> (Capture
                                                                                                                                                                                      "tid"
                                                                                                                                                                                      TeamId
                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                        :> ("validate-saml-emails"
                                                                                                                                                                                            :> Get
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                                 :<|> Named
                                                                                                                                                        '("get-deprecated",
                                                                                                                                                          DigitalSignaturesConfig)
                                                                                                                                                        (ZUser
                                                                                                                                                         :> (Summary
                                                                                                                                                               "[deprecated] Get config for digitalSignatures"
                                                                                                                                                             :> (Until
                                                                                                                                                                   'V2
                                                                                                                                                                 :> (Description
                                                                                                                                                                       "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("teams"
                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                           "tid"
                                                                                                                                                                                           TeamId
                                                                                                                                                                                         :> ("features"
                                                                                                                                                                                             :> ("digital-signatures"
                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         DigitalSignaturesConfig)))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              LegalholdConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature legalhold"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("legalhold"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     LegalholdConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    SSOConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature sso"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("sso"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           SSOConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          SearchVisibilityAvailableConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("searchVisibility"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 SearchVisibilityAvailableConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                ValidateSAMLEmailsConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("validateSAMLemails"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      DigitalSignaturesConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("digitalSignatures"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             DigitalSignaturesConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            AppLockConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature appLock"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("appLock"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   AppLockConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  FileSharingConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("fileSharing"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         FileSharingConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        ClassifiedDomainsConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("classifiedDomains"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               ClassifiedDomainsConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              ConferenceCallingConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("conferenceCalling"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     ConferenceCallingConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    SelfDeletingMessagesConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("selfDeletingMessages"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        '("get-config",
                                                                                                                                                                                                          GuestLinksConfig)
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                 GuestLinksConfig))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              '("get-config",
                                                                                                                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                                       SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                            :<|> Named
                                                                                                                                                                                                                   '("get-config",
                                                                                                                                                                                                                     MLSConfig)
                                                                                                                                                                                                                   (Summary
                                                                                                                                                                                                                      "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                                    :> (Until
                                                                                                                                                                                                                          'V2
                                                                                                                                                                                                                        :> (Description
                                                                                                                                                                                                                              "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                            :> (ZUser
                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                                                                            :> ("feature-configs"
                                                                                                                                                                                                                                                :> ("mls"
                                                                                                                                                                                                                                                    :> Get
                                                                                                                                                                                                                                                         '[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
        "set-search-visibility"
        (Summary "Sets the search visibility for the whole team"
         :> (CanThrow 'NotATeamMember
             :> (CanThrow OperationDenied
                 :> (CanThrow 'TeamSearchVisibilityNotEnabled
                     :> (CanThrow 'TeamNotFound
                         :> (CanThrow TeamFeatureError
                             :> (ZLocalUser
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("search-visibility"
                                             :> (ReqBody '[JSON] TeamSearchVisibilityView
                                                 :> MultiVerb
                                                      'PUT
                                                      '[JSON]
                                                      '[RespondEmpty 204 "Search visibility set"]
                                                      ())))))))))))
      :<|> (Named
              '("get", ValidateSAMLEmailsConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Get config for validateSAMLemails"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> ("teams"
                                       :> (Capture "tid" TeamId
                                           :> ("features"
                                               :> ("validateSAMLemails"
                                                   :> Get
                                                        '[JSON]
                                                        (LockableFeature
                                                           ValidateSAMLEmailsConfig)))))))))))
            :<|> (Named
                    '("get", DigitalSignaturesConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Get config for digitalSignatures"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("digitalSignatures"
                                                         :> Get
                                                              '[JSON]
                                                              (LockableFeature
                                                                 DigitalSignaturesConfig)))))))))))
                  :<|> ((Named
                           '("get", AppLockConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for appLock"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("appLock"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        AppLockConfig)))))))))))
                         :<|> Named
                                '("put", AppLockConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for appLock"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("appLock"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      AppLockConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         AppLockConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", FileSharingConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for fileSharing"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("fileSharing"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              FileSharingConfig)))))))))))
                               :<|> Named
                                      '("put", FileSharingConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for fileSharing"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("fileSharing"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            FileSharingConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               FileSharingConfig)))))))))))))))
                              :<|> (Named
                                      '("get", ClassifiedDomainsConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Get config for classifiedDomains"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("classifiedDomains"
                                                                           :> Get
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   ClassifiedDomainsConfig)))))))))))
                                    :<|> ((Named
                                             '("get", ConferenceCallingConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary "Get config for conferenceCalling"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("conferenceCalling"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          ConferenceCallingConfig)))))))))))
                                           :<|> Named
                                                  '("put", ConferenceCallingConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for conferenceCalling"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("conferenceCalling"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        ConferenceCallingConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           ConferenceCallingConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", SelfDeletingMessagesConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for selfDeletingMessages"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("selfDeletingMessages"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                SelfDeletingMessagesConfig)))))))))))
                                                 :<|> Named
                                                        '("put", SelfDeletingMessagesConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for selfDeletingMessages"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("selfDeletingMessages"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              SelfDeletingMessagesConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 SelfDeletingMessagesConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", GuestLinksConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for conversationGuestLinks"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("conversationGuestLinks"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      GuestLinksConfig)))))))))))
                                                       :<|> Named
                                                              '("put", GuestLinksConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for conversationGuestLinks"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("conversationGuestLinks"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    GuestLinksConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       GuestLinksConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get",
                                                                 SndFactorPasswordChallengeConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for sndFactorPasswordChallenge"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("sndFactorPasswordChallenge"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            SndFactorPasswordChallengeConfig)))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      SndFactorPasswordChallengeConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for sndFactorPasswordChallenge"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             SndFactorPasswordChallengeConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get", MLSConfig)
                                                                     (From 'V5
                                                                      :> (Description ""
                                                                          :> (ZUser
                                                                              :> (Summary
                                                                                    "Get config for mls"
                                                                                  :> (CanThrow
                                                                                        OperationDenied
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mls"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      MLSConfig))))))))))))
                                                                   :<|> Named
                                                                          '("put", MLSConfig)
                                                                          (From 'V5
                                                                           :> (Description ""
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Put config for mls"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("mls"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (Feature
                                                                                                                                    MLSConfig)
                                                                                                                               :> Put
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       MLSConfig))))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             ExposeInvitationURLsToTeamAdminConfig)
                                                                           (Description ""
                                                                            :> (ZUser
                                                                                :> (Summary
                                                                                      "Get config for exposeInvitationURLsToTeamAdmin"
                                                                                    :> (CanThrow
                                                                                          OperationDenied
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                :> Get
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                (Description ""
                                                                                 :> (ZUser
                                                                                     :> (Summary
                                                                                           "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (Feature
                                                                                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                                 :> Put
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get",
                                                                                   SearchVisibilityInboundConfig)
                                                                                 (Description ""
                                                                                  :> (ZUser
                                                                                      :> (Summary
                                                                                            "Get config for searchVisibilityInbound"
                                                                                          :> (CanThrow
                                                                                                OperationDenied
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("searchVisibilityInbound"
                                                                                                                      :> Get
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              SearchVisibilityInboundConfig)))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        SearchVisibilityInboundConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (ZUser
                                                                                           :> (Summary
                                                                                                 "Put config for searchVisibilityInbound"
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 TeamFeatureError
                                                                                                               :> (CanThrowMany
                                                                                                                     '[]
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("searchVisibilityInbound"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         (Feature
                                                                                                                                            SearchVisibilityInboundConfig)
                                                                                                                                       :> Put
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               SearchVisibilityInboundConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("get",
                                                                                         OutlookCalIntegrationConfig)
                                                                                       (Description
                                                                                          ""
                                                                                        :> (ZUser
                                                                                            :> (Summary
                                                                                                  "Get config for outlookCalIntegration"
                                                                                                :> (CanThrow
                                                                                                      OperationDenied
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              'TeamNotFound
                                                                                                            :> ("teams"
                                                                                                                :> (Capture
                                                                                                                      "tid"
                                                                                                                      TeamId
                                                                                                                    :> ("features"
                                                                                                                        :> ("outlookCalIntegration"
                                                                                                                            :> Get
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    OutlookCalIntegrationConfig)))))))))))
                                                                                     :<|> Named
                                                                                            '("put",
                                                                                              OutlookCalIntegrationConfig)
                                                                                            (Description
                                                                                               ""
                                                                                             :> (ZUser
                                                                                                 :> (Summary
                                                                                                       "Put config for outlookCalIntegration"
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   'TeamNotFound
                                                                                                                 :> (CanThrow
                                                                                                                       TeamFeatureError
                                                                                                                     :> (CanThrowMany
                                                                                                                           '[]
                                                                                                                         :> ("teams"
                                                                                                                             :> (Capture
                                                                                                                                   "tid"
                                                                                                                                   TeamId
                                                                                                                                 :> ("features"
                                                                                                                                     :> ("outlookCalIntegration"
                                                                                                                                         :> (ReqBody
                                                                                                                                               '[JSON]
                                                                                                                                               (Feature
                                                                                                                                                  OutlookCalIntegrationConfig)
                                                                                                                                             :> Put
                                                                                                                                                  '[JSON]
                                                                                                                                                  (LockableFeature
                                                                                                                                                     OutlookCalIntegrationConfig)))))))))))))))
                                                                                    :<|> (Named
                                                                                            '("get",
                                                                                              MlsE2EIdConfig)
                                                                                            (From
                                                                                               'V5
                                                                                             :> (Description
                                                                                                   ""
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Get config for mlsE2EId"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("mlsE2EId"
                                                                                                                                     :> Get
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             MlsE2EIdConfig))))))))))))
                                                                                          :<|> (Named
                                                                                                  "put-MlsE2EIdConfig@v5"
                                                                                                  (From
                                                                                                     'V5
                                                                                                   :> (Until
                                                                                                         'V6
                                                                                                       :> (ZUser
                                                                                                           :> (Summary
                                                                                                                 "Put config for mlsE2EId"
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("mlsE2EId"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (Feature
                                                                                                                                                            MlsE2EIdConfig)
                                                                                                                                                       :> Put
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               MlsE2EIdConfig)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        '("put",
                                                                                                          MlsE2EIdConfig)
                                                                                                        (From
                                                                                                           'V6
                                                                                                         :> (Description
                                                                                                               ""
                                                                                                             :> (ZUser
                                                                                                                 :> (Summary
                                                                                                                       "Put config for mlsE2EId"
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("mlsE2EId"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (Feature
                                                                                                                                                                  MlsE2EIdConfig)
                                                                                                                                                             :> Put
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     MlsE2EIdConfig)))))))))))))))
                                                                                                      :<|> ((Named
                                                                                                               '("get",
                                                                                                                 MlsMigrationConfig)
                                                                                                               (From
                                                                                                                  'V5
                                                                                                                :> (Description
                                                                                                                      ""
                                                                                                                    :> (ZUser
                                                                                                                        :> (Summary
                                                                                                                              "Get config for mlsMigration"
                                                                                                                            :> (CanThrow
                                                                                                                                  OperationDenied
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("mlsMigration"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                MlsMigrationConfig))))))))))))
                                                                                                             :<|> Named
                                                                                                                    '("put",
                                                                                                                      MlsMigrationConfig)
                                                                                                                    (From
                                                                                                                       'V5
                                                                                                                     :> (Description
                                                                                                                           ""
                                                                                                                         :> (ZUser
                                                                                                                             :> (Summary
                                                                                                                                   "Put config for mlsMigration"
                                                                                                                                 :> (CanThrow
                                                                                                                                       OperationDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("mlsMigration"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (Feature
                                                                                                                                                                              MlsMigrationConfig)
                                                                                                                                                                         :> Put
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 MlsMigrationConfig))))))))))))))))
                                                                                                            :<|> ((Named
                                                                                                                     '("get",
                                                                                                                       EnforceFileDownloadLocationConfig)
                                                                                                                     (From
                                                                                                                        'V5
                                                                                                                      :> (Description
                                                                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                          :> (ZUser
                                                                                                                              :> (Summary
                                                                                                                                    "Get config for enforceFileDownloadLocation"
                                                                                                                                  :> (CanThrow
                                                                                                                                        OperationDenied
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      EnforceFileDownloadLocationConfig))))))))))))
                                                                                                                   :<|> Named
                                                                                                                          '("put",
                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                          (From
                                                                                                                             'V5
                                                                                                                           :> (Description
                                                                                                                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                               :> (ZUser
                                                                                                                                   :> (Summary
                                                                                                                                         "Put config for enforceFileDownloadLocation"
                                                                                                                                       :> (CanThrow
                                                                                                                                             OperationDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         TeamFeatureError
                                                                                                                                                       :> (CanThrowMany
                                                                                                                                                             '[]
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> ("enforceFileDownloadLocation"
                                                                                                                                                                           :> (ReqBody
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (Feature
                                                                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                                                                               :> Put
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get",
                                                                                                                            LimitedEventFanoutConfig)
                                                                                                                          (From
                                                                                                                             'V5
                                                                                                                           :> (Description
                                                                                                                                 ""
                                                                                                                               :> (ZUser
                                                                                                                                   :> (Summary
                                                                                                                                         "Get config for limitedEventFanout"
                                                                                                                                       :> (CanThrow
                                                                                                                                             OperationDenied
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("teams"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "tid"
                                                                                                                                                             TeamId
                                                                                                                                                           :> ("features"
                                                                                                                                                               :> ("limitedEventFanout"
                                                                                                                                                                   :> Get
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           LimitedEventFanoutConfig))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-all-feature-configs-for-user"
                                                                                                                                (Summary
                                                                                                                                   "Gets feature configs for a user"
                                                                                                                                 :> (Description
                                                                                                                                       "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                                     :> (DescriptionOAuthScope
                                                                                                                                           'ReadFeatureConfigs
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> Get
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  AllTeamFeatures))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      "get-all-feature-configs-for-team"
                                                                                                                                      (Summary
                                                                                                                                         "Gets feature configs for a team"
                                                                                                                                       :> (Description
                                                                                                                                             "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                                           :> (CanThrow
                                                                                                                                                 'NotATeamMember
                                                                                                                                               :> (CanThrow
                                                                                                                                                     OperationDenied
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'TeamNotFound
                                                                                                                                                       :> (ZLocalUser
                                                                                                                                                           :> ("teams"
                                                                                                                                                               :> (Capture
                                                                                                                                                                     "tid"
                                                                                                                                                                     TeamId
                                                                                                                                                                   :> ("features"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            AllTeamFeatures)))))))))
                                                                                                                                    :<|> ((Named
                                                                                                                                             '("get-deprecated",
                                                                                                                                               SearchVisibilityAvailableConfig)
                                                                                                                                             (ZUser
                                                                                                                                              :> (Summary
                                                                                                                                                    "[deprecated] Get config for searchVisibility"
                                                                                                                                                  :> (Until
                                                                                                                                                        'V2
                                                                                                                                                      :> (Description
                                                                                                                                                            "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'NotATeamMember
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    OperationDenied
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("search-visibility"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              SearchVisibilityAvailableConfig))))))))))))
                                                                                                                                           :<|> (Named
                                                                                                                                                   '("put-deprecated",
                                                                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                                                                   (ZUser
                                                                                                                                                    :> (Summary
                                                                                                                                                          "[deprecated] Get config for searchVisibility"
                                                                                                                                                        :> (Until
                                                                                                                                                              'V2
                                                                                                                                                            :> (Description
                                                                                                                                                                  "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          OperationDenied
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  TeamFeatureError
                                                                                                                                                                                :> ("teams"
                                                                                                                                                                                    :> (Capture
                                                                                                                                                                                          "tid"
                                                                                                                                                                                          TeamId
                                                                                                                                                                                        :> ("features"
                                                                                                                                                                                            :> ("search-visibility"
                                                                                                                                                                                                :> (ReqBody
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (Feature
                                                                                                                                                                                                         SearchVisibilityAvailableConfig)
                                                                                                                                                                                                    :> Put
                                                                                                                                                                                                         '[JSON]
                                                                                                                                                                                                         (LockableFeature
                                                                                                                                                                                                            SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                                                 :<|> (Named
                                                                                                                                                         '("get-deprecated",
                                                                                                                                                           ValidateSAMLEmailsConfig)
                                                                                                                                                         (ZUser
                                                                                                                                                          :> (Summary
                                                                                                                                                                "[deprecated] Get config for validateSAMLemails"
                                                                                                                                                              :> (Until
                                                                                                                                                                    'V2
                                                                                                                                                                  :> (Description
                                                                                                                                                                        "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                OperationDenied
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                  :> ("teams"
                                                                                                                                                                                      :> (Capture
                                                                                                                                                                                            "tid"
                                                                                                                                                                                            TeamId
                                                                                                                                                                                          :> ("features"
                                                                                                                                                                                              :> ("validate-saml-emails"
                                                                                                                                                                                                  :> Get
                                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                                          ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                                       :<|> Named
                                                                                                                                                              '("get-deprecated",
                                                                                                                                                                DigitalSignaturesConfig)
                                                                                                                                                              (ZUser
                                                                                                                                                               :> (Summary
                                                                                                                                                                     "[deprecated] Get config for digitalSignatures"
                                                                                                                                                                   :> (Until
                                                                                                                                                                         'V2
                                                                                                                                                                       :> (Description
                                                                                                                                                                             "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("teams"
                                                                                                                                                                                           :> (Capture
                                                                                                                                                                                                 "tid"
                                                                                                                                                                                                 TeamId
                                                                                                                                                                                               :> ("features"
                                                                                                                                                                                                   :> ("digital-signatures"
                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                               DigitalSignaturesConfig)))))))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    LegalholdConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature legalhold"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("legalhold"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           LegalholdConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          SSOConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature sso"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("sso"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 SSOConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                SearchVisibilityAvailableConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("searchVisibility"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       SearchVisibilityAvailableConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      ValidateSAMLEmailsConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("validateSAMLemails"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            DigitalSignaturesConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("digitalSignatures"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   DigitalSignaturesConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  AppLockConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature appLock"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("appLock"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         AppLockConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        FileSharingConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("fileSharing"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               FileSharingConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              ClassifiedDomainsConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("classifiedDomains"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     ClassifiedDomainsConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    ConferenceCallingConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("conferenceCalling"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           ConferenceCallingConfig))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        '("get-config",
                                                                                                                                                                                                          SelfDeletingMessagesConfig)
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                                                                     :> ("selfDeletingMessages"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                 SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              '("get-config",
                                                                                                                                                                                                                GuestLinksConfig)
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                                       GuestLinksConfig))))))))))
                                                                                                                                                                                                            :<|> (Named
                                                                                                                                                                                                                    '("get-config",
                                                                                                                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                                    (Summary
                                                                                                                                                                                                                       "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                                     :> (Until
                                                                                                                                                                                                                           'V2
                                                                                                                                                                                                                         :> (Description
                                                                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                                                                             SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                                  :<|> Named
                                                                                                                                                                                                                         '("get-config",
                                                                                                                                                                                                                           MLSConfig)
                                                                                                                                                                                                                         (Summary
                                                                                                                                                                                                                            "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                                          :> (Until
                                                                                                                                                                                                                                'V2
                                                                                                                                                                                                                              :> (Description
                                                                                                                                                                                                                                    "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                                  :> (ZUser
                                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                                                                  :> ("feature-configs"
                                                                                                                                                                                                                                                      :> ("mls"
                                                                                                                                                                                                                                                          :> Get
                                                                                                                                                                                                                                                               '[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 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", ValidateSAMLEmailsConfig) ServerT
  (Description ""
   :> (ZUser
       :> (Summary "Get config for validateSAMLemails"
           :> (CanThrow OperationDenied
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow 'TeamNotFound
                       :> ("teams"
                           :> (Capture "tid" TeamId
                               :> ("features"
                                   :> ("validateSAMLemails"
                                       :> Get
                                            '[JSON]
                                            (LockableFeature ValidateSAMLEmailsConfig)))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Description ""
            :> (ZUser
                :> (Summary "Get config for validateSAMLemails"
                    :> (CanThrow OperationDenied
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("validateSAMLemails"
                                                :> Get
                                                     '[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]))
UserId
-> TeamId
-> Sem
     '[Error (Tagged OperationDenied ()),
       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]
     (LockableFeature ValidateSAMLEmailsConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member TeamFeatureStore r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member TeamStore r) =>
UserId -> TeamId -> Sem r (LockableFeature cfg)
getFeature
    API
  (Named
     '("get", ValidateSAMLEmailsConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for validateSAMLemails"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("validateSAMLemails"
                                          :> Get
                                               '[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
        '("get", DigitalSignaturesConfig)
        (Description ""
         :> (ZUser
             :> (Summary "Get config for digitalSignatures"
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> ("digitalSignatures"
                                             :> Get
                                                  '[JSON]
                                                  (LockableFeature
                                                     DigitalSignaturesConfig)))))))))))
      :<|> ((Named
               '("get", AppLockConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for appLock"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("appLock"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature AppLockConfig)))))))))))
             :<|> Named
                    '("put", AppLockConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for appLock"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("appLock"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature AppLockConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             AppLockConfig)))))))))))))))
            :<|> ((Named
                     '("get", FileSharingConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for fileSharing"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("fileSharing"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  FileSharingConfig)))))))))))
                   :<|> Named
                          '("put", FileSharingConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for fileSharing"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("fileSharing"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                FileSharingConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   FileSharingConfig)))))))))))))))
                  :<|> (Named
                          '("get", ClassifiedDomainsConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Get config for classifiedDomains"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("classifiedDomains"
                                                               :> Get
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       ClassifiedDomainsConfig)))))))))))
                        :<|> ((Named
                                 '("get", ConferenceCallingConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for conferenceCalling"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("conferenceCalling"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              ConferenceCallingConfig)))))))))))
                               :<|> Named
                                      '("put", ConferenceCallingConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for conferenceCalling"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("conferenceCalling"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            ConferenceCallingConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               ConferenceCallingConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", SelfDeletingMessagesConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for selfDeletingMessages"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("selfDeletingMessages"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    SelfDeletingMessagesConfig)))))))))))
                                     :<|> Named
                                            '("put", SelfDeletingMessagesConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Put config for selfDeletingMessages"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("selfDeletingMessages"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  SelfDeletingMessagesConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     SelfDeletingMessagesConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", GuestLinksConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary
                                                        "Get config for conversationGuestLinks"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("conversationGuestLinks"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          GuestLinksConfig)))))))))))
                                           :<|> Named
                                                  '("put", GuestLinksConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for conversationGuestLinks"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("conversationGuestLinks"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        GuestLinksConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           GuestLinksConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", SndFactorPasswordChallengeConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for sndFactorPasswordChallenge"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("sndFactorPasswordChallenge"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                SndFactorPasswordChallengeConfig)))))))))))
                                                 :<|> Named
                                                        '("put", SndFactorPasswordChallengeConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for sndFactorPasswordChallenge"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              SndFactorPasswordChallengeConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 SndFactorPasswordChallengeConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", MLSConfig)
                                                         (From 'V5
                                                          :> (Description ""
                                                              :> (ZUser
                                                                  :> (Summary "Get config for mls"
                                                                      :> (CanThrow OperationDenied
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mls"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          MLSConfig))))))))))))
                                                       :<|> Named
                                                              '("put", MLSConfig)
                                                              (From 'V5
                                                               :> (Description ""
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Put config for mls"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("mls"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (Feature
                                                                                                                        MLSConfig)
                                                                                                                   :> Put
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           MLSConfig))))))))))))))))
                                                      :<|> ((Named
                                                               '("get",
                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for exposeInvitationURLsToTeamAdmin"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for exposeInvitationURLsToTeamAdmin"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get",
                                                                       SearchVisibilityInboundConfig)
                                                                     (Description ""
                                                                      :> (ZUser
                                                                          :> (Summary
                                                                                "Get config for searchVisibilityInbound"
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("searchVisibilityInbound"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  SearchVisibilityInboundConfig)))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            SearchVisibilityInboundConfig)
                                                                          (Description ""
                                                                           :> (ZUser
                                                                               :> (Summary
                                                                                     "Put config for searchVisibilityInbound"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("searchVisibilityInbound"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                SearchVisibilityInboundConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   SearchVisibilityInboundConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             OutlookCalIntegrationConfig)
                                                                           (Description ""
                                                                            :> (ZUser
                                                                                :> (Summary
                                                                                      "Get config for outlookCalIntegration"
                                                                                    :> (CanThrow
                                                                                          OperationDenied
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("outlookCalIntegration"
                                                                                                                :> Get
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        OutlookCalIntegrationConfig)))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  OutlookCalIntegrationConfig)
                                                                                (Description ""
                                                                                 :> (ZUser
                                                                                     :> (Summary
                                                                                           "Put config for outlookCalIntegration"
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("outlookCalIntegration"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (Feature
                                                                                                                                      OutlookCalIntegrationConfig)
                                                                                                                                 :> Put
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         OutlookCalIntegrationConfig)))))))))))))))
                                                                        :<|> (Named
                                                                                '("get",
                                                                                  MlsE2EIdConfig)
                                                                                (From 'V5
                                                                                 :> (Description ""
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Get config for mlsE2EId"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("mlsE2EId"
                                                                                                                         :> Get
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 MlsE2EIdConfig))))))))))))
                                                                              :<|> (Named
                                                                                      "put-MlsE2EIdConfig@v5"
                                                                                      (From 'V5
                                                                                       :> (Until 'V6
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Put config for mlsE2EId"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("mlsE2EId"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (Feature
                                                                                                                                                MlsE2EIdConfig)
                                                                                                                                           :> Put
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   MlsE2EIdConfig)))))))))))))))
                                                                                    :<|> (Named
                                                                                            '("put",
                                                                                              MlsE2EIdConfig)
                                                                                            (From
                                                                                               'V6
                                                                                             :> (Description
                                                                                                   ""
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Put config for mlsE2EId"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("mlsE2EId"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (Feature
                                                                                                                                                      MlsE2EIdConfig)
                                                                                                                                                 :> Put
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MlsE2EIdConfig)))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("get",
                                                                                                     MlsMigrationConfig)
                                                                                                   (From
                                                                                                      'V5
                                                                                                    :> (Description
                                                                                                          ""
                                                                                                        :> (ZUser
                                                                                                            :> (Summary
                                                                                                                  "Get config for mlsMigration"
                                                                                                                :> (CanThrow
                                                                                                                      OperationDenied
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mlsMigration"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    MlsMigrationConfig))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("put",
                                                                                                          MlsMigrationConfig)
                                                                                                        (From
                                                                                                           'V5
                                                                                                         :> (Description
                                                                                                               ""
                                                                                                             :> (ZUser
                                                                                                                 :> (Summary
                                                                                                                       "Put config for mlsMigration"
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("mlsMigration"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (Feature
                                                                                                                                                                  MlsMigrationConfig)
                                                                                                                                                             :> Put
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     MlsMigrationConfig))))))))))))))))
                                                                                                :<|> ((Named
                                                                                                         '("get",
                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                         (From
                                                                                                            'V5
                                                                                                          :> (Description
                                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                              :> (ZUser
                                                                                                                  :> (Summary
                                                                                                                        "Get config for enforceFileDownloadLocation"
                                                                                                                      :> (CanThrow
                                                                                                                            OperationDenied
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          EnforceFileDownloadLocationConfig))))))))))))
                                                                                                       :<|> Named
                                                                                                              '("put",
                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                              (From
                                                                                                                 'V5
                                                                                                               :> (Description
                                                                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                   :> (ZUser
                                                                                                                       :> (Summary
                                                                                                                             "Put config for enforceFileDownloadLocation"
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("enforceFileDownloadLocation"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (Feature
                                                                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                                                                   :> Put
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get",
                                                                                                                LimitedEventFanoutConfig)
                                                                                                              (From
                                                                                                                 'V5
                                                                                                               :> (Description
                                                                                                                     ""
                                                                                                                   :> (ZUser
                                                                                                                       :> (Summary
                                                                                                                             "Get config for limitedEventFanout"
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("limitedEventFanout"
                                                                                                                                                       :> Get
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               LimitedEventFanoutConfig))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-all-feature-configs-for-user"
                                                                                                                    (Summary
                                                                                                                       "Gets feature configs for a user"
                                                                                                                     :> (Description
                                                                                                                           "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                               'ReadFeatureConfigs
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> Get
                                                                                                                                                      '[JSON]
                                                                                                                                                      AllTeamFeatures))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-all-feature-configs-for-team"
                                                                                                                          (Summary
                                                                                                                             "Gets feature configs for a team"
                                                                                                                           :> (Description
                                                                                                                                 "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         OperationDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TeamNotFound
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                AllTeamFeatures)))))))))
                                                                                                                        :<|> ((Named
                                                                                                                                 '("get-deprecated",
                                                                                                                                   SearchVisibilityAvailableConfig)
                                                                                                                                 (ZUser
                                                                                                                                  :> (Summary
                                                                                                                                        "[deprecated] Get config for searchVisibility"
                                                                                                                                      :> (Until
                                                                                                                                            'V2
                                                                                                                                          :> (Description
                                                                                                                                                "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'NotATeamMember
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        OperationDenied
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("search-visibility"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  SearchVisibilityAvailableConfig))))))))))))
                                                                                                                               :<|> (Named
                                                                                                                                       '("put-deprecated",
                                                                                                                                         SearchVisibilityAvailableConfig)
                                                                                                                                       (ZUser
                                                                                                                                        :> (Summary
                                                                                                                                              "[deprecated] Get config for searchVisibility"
                                                                                                                                            :> (Until
                                                                                                                                                  'V2
                                                                                                                                                :> (Description
                                                                                                                                                      "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'NotATeamMember
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              OperationDenied
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> ("teams"
                                                                                                                                                                        :> (Capture
                                                                                                                                                                              "tid"
                                                                                                                                                                              TeamId
                                                                                                                                                                            :> ("features"
                                                                                                                                                                                :> ("search-visibility"
                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (Feature
                                                                                                                                                                                             SearchVisibilityAvailableConfig)
                                                                                                                                                                                        :> Put
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                                     :<|> (Named
                                                                                                                                             '("get-deprecated",
                                                                                                                                               ValidateSAMLEmailsConfig)
                                                                                                                                             (ZUser
                                                                                                                                              :> (Summary
                                                                                                                                                    "[deprecated] Get config for validateSAMLemails"
                                                                                                                                                  :> (Until
                                                                                                                                                        'V2
                                                                                                                                                      :> (Description
                                                                                                                                                            "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'NotATeamMember
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    OperationDenied
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("validate-saml-emails"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                           :<|> Named
                                                                                                                                                  '("get-deprecated",
                                                                                                                                                    DigitalSignaturesConfig)
                                                                                                                                                  (ZUser
                                                                                                                                                   :> (Summary
                                                                                                                                                         "[deprecated] Get config for digitalSignatures"
                                                                                                                                                       :> (Until
                                                                                                                                                             'V2
                                                                                                                                                           :> (Description
                                                                                                                                                                 "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("teams"
                                                                                                                                                                               :> (Capture
                                                                                                                                                                                     "tid"
                                                                                                                                                                                     TeamId
                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                       :> ("digital-signatures"
                                                                                                                                                                                           :> Get
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   DigitalSignaturesConfig)))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        LegalholdConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature legalhold"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("legalhold"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               LegalholdConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              SSOConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature sso"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("sso"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     SSOConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    SearchVisibilityAvailableConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("searchVisibility"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           SearchVisibilityAvailableConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          ValidateSAMLEmailsConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("validateSAMLemails"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                DigitalSignaturesConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("digitalSignatures"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       DigitalSignaturesConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      AppLockConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature appLock"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("appLock"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             AppLockConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            FileSharingConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("fileSharing"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   FileSharingConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  ClassifiedDomainsConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("classifiedDomains"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         ClassifiedDomainsConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        ConferenceCallingConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("conferenceCalling"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               ConferenceCallingConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              SelfDeletingMessagesConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("selfDeletingMessages"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    GuestLinksConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           GuestLinksConfig))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        '("get-config",
                                                                                                                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                 SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                      :<|> Named
                                                                                                                                                                                                             '("get-config",
                                                                                                                                                                                                               MLSConfig)
                                                                                                                                                                                                             (Summary
                                                                                                                                                                                                                "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                              :> (Until
                                                                                                                                                                                                                    'V2
                                                                                                                                                                                                                  :> (Description
                                                                                                                                                                                                                        "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                      :> (ZUser
                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                                                                      :> ("feature-configs"
                                                                                                                                                                                                                                          :> ("mls"
                                                                                                                                                                                                                                              :> Get
                                                                                                                                                                                                                                                   '[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
        '("get", ValidateSAMLEmailsConfig)
        (Description ""
         :> (ZUser
             :> (Summary "Get config for validateSAMLemails"
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> ("validateSAMLemails"
                                             :> Get
                                                  '[JSON]
                                                  (LockableFeature
                                                     ValidateSAMLEmailsConfig)))))))))))
      :<|> (Named
              '("get", DigitalSignaturesConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Get config for digitalSignatures"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> ("teams"
                                       :> (Capture "tid" TeamId
                                           :> ("features"
                                               :> ("digitalSignatures"
                                                   :> Get
                                                        '[JSON]
                                                        (LockableFeature
                                                           DigitalSignaturesConfig)))))))))))
            :<|> ((Named
                     '("get", AppLockConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for appLock"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("appLock"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  AppLockConfig)))))))))))
                   :<|> Named
                          '("put", AppLockConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for appLock"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("appLock"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature AppLockConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   AppLockConfig)))))))))))))))
                  :<|> ((Named
                           '("get", FileSharingConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for fileSharing"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("fileSharing"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        FileSharingConfig)))))))))))
                         :<|> Named
                                '("put", FileSharingConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for fileSharing"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("fileSharing"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      FileSharingConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         FileSharingConfig)))))))))))))))
                        :<|> (Named
                                '("get", ClassifiedDomainsConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Get config for classifiedDomains"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("classifiedDomains"
                                                                     :> Get
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             ClassifiedDomainsConfig)))))))))))
                              :<|> ((Named
                                       '("get", ConferenceCallingConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for conferenceCalling"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("conferenceCalling"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    ConferenceCallingConfig)))))))))))
                                     :<|> Named
                                            '("put", ConferenceCallingConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Put config for conferenceCalling"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("conferenceCalling"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  ConferenceCallingConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     ConferenceCallingConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", SelfDeletingMessagesConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary "Get config for selfDeletingMessages"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("selfDeletingMessages"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          SelfDeletingMessagesConfig)))))))))))
                                           :<|> Named
                                                  '("put", SelfDeletingMessagesConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for selfDeletingMessages"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("selfDeletingMessages"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        SelfDeletingMessagesConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           SelfDeletingMessagesConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", GuestLinksConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for conversationGuestLinks"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("conversationGuestLinks"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                GuestLinksConfig)))))))))))
                                                 :<|> Named
                                                        '("put", GuestLinksConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for conversationGuestLinks"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("conversationGuestLinks"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              GuestLinksConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 GuestLinksConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", SndFactorPasswordChallengeConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for sndFactorPasswordChallenge"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("sndFactorPasswordChallenge"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      SndFactorPasswordChallengeConfig)))))))))))
                                                       :<|> Named
                                                              '("put",
                                                                SndFactorPasswordChallengeConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for sndFactorPasswordChallenge"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       SndFactorPasswordChallengeConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get", MLSConfig)
                                                               (From 'V5
                                                                :> (Description ""
                                                                    :> (ZUser
                                                                        :> (Summary
                                                                              "Get config for mls"
                                                                            :> (CanThrow
                                                                                  OperationDenied
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mls"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                MLSConfig))))))))))))
                                                             :<|> Named
                                                                    '("put", MLSConfig)
                                                                    (From 'V5
                                                                     :> (Description ""
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Put config for mls"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("mls"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (Feature
                                                                                                                              MLSConfig)
                                                                                                                         :> Put
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 MLSConfig))))))))))))))))
                                                            :<|> ((Named
                                                                     '("get",
                                                                       ExposeInvitationURLsToTeamAdminConfig)
                                                                     (Description ""
                                                                      :> (ZUser
                                                                          :> (Summary
                                                                                "Get config for exposeInvitationURLsToTeamAdmin"
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                          (Description ""
                                                                           :> (ZUser
                                                                               :> (Summary
                                                                                     "Put config for exposeInvitationURLsToTeamAdmin"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             SearchVisibilityInboundConfig)
                                                                           (Description ""
                                                                            :> (ZUser
                                                                                :> (Summary
                                                                                      "Get config for searchVisibilityInbound"
                                                                                    :> (CanThrow
                                                                                          OperationDenied
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("searchVisibilityInbound"
                                                                                                                :> Get
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        SearchVisibilityInboundConfig)))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  SearchVisibilityInboundConfig)
                                                                                (Description ""
                                                                                 :> (ZUser
                                                                                     :> (Summary
                                                                                           "Put config for searchVisibilityInbound"
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("searchVisibilityInbound"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (Feature
                                                                                                                                      SearchVisibilityInboundConfig)
                                                                                                                                 :> Put
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         SearchVisibilityInboundConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get",
                                                                                   OutlookCalIntegrationConfig)
                                                                                 (Description ""
                                                                                  :> (ZUser
                                                                                      :> (Summary
                                                                                            "Get config for outlookCalIntegration"
                                                                                          :> (CanThrow
                                                                                                OperationDenied
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        'TeamNotFound
                                                                                                      :> ("teams"
                                                                                                          :> (Capture
                                                                                                                "tid"
                                                                                                                TeamId
                                                                                                              :> ("features"
                                                                                                                  :> ("outlookCalIntegration"
                                                                                                                      :> Get
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              OutlookCalIntegrationConfig)))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        OutlookCalIntegrationConfig)
                                                                                      (Description
                                                                                         ""
                                                                                       :> (ZUser
                                                                                           :> (Summary
                                                                                                 "Put config for outlookCalIntegration"
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             'TeamNotFound
                                                                                                           :> (CanThrow
                                                                                                                 TeamFeatureError
                                                                                                               :> (CanThrowMany
                                                                                                                     '[]
                                                                                                                   :> ("teams"
                                                                                                                       :> (Capture
                                                                                                                             "tid"
                                                                                                                             TeamId
                                                                                                                           :> ("features"
                                                                                                                               :> ("outlookCalIntegration"
                                                                                                                                   :> (ReqBody
                                                                                                                                         '[JSON]
                                                                                                                                         (Feature
                                                                                                                                            OutlookCalIntegrationConfig)
                                                                                                                                       :> Put
                                                                                                                                            '[JSON]
                                                                                                                                            (LockableFeature
                                                                                                                                               OutlookCalIntegrationConfig)))))))))))))))
                                                                              :<|> (Named
                                                                                      '("get",
                                                                                        MlsE2EIdConfig)
                                                                                      (From 'V5
                                                                                       :> (Description
                                                                                             ""
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Get config for mlsE2EId"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("mlsE2EId"
                                                                                                                               :> Get
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       MlsE2EIdConfig))))))))))))
                                                                                    :<|> (Named
                                                                                            "put-MlsE2EIdConfig@v5"
                                                                                            (From
                                                                                               'V5
                                                                                             :> (Until
                                                                                                   'V6
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Put config for mlsE2EId"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("mlsE2EId"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (Feature
                                                                                                                                                      MlsE2EIdConfig)
                                                                                                                                                 :> Put
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MlsE2EIdConfig)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  '("put",
                                                                                                    MlsE2EIdConfig)
                                                                                                  (From
                                                                                                     'V6
                                                                                                   :> (Description
                                                                                                         ""
                                                                                                       :> (ZUser
                                                                                                           :> (Summary
                                                                                                                 "Put config for mlsE2EId"
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("mlsE2EId"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (Feature
                                                                                                                                                            MlsE2EIdConfig)
                                                                                                                                                       :> Put
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               MlsE2EIdConfig)))))))))))))))
                                                                                                :<|> ((Named
                                                                                                         '("get",
                                                                                                           MlsMigrationConfig)
                                                                                                         (From
                                                                                                            'V5
                                                                                                          :> (Description
                                                                                                                ""
                                                                                                              :> (ZUser
                                                                                                                  :> (Summary
                                                                                                                        "Get config for mlsMigration"
                                                                                                                      :> (CanThrow
                                                                                                                            OperationDenied
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("mlsMigration"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          MlsMigrationConfig))))))))))))
                                                                                                       :<|> Named
                                                                                                              '("put",
                                                                                                                MlsMigrationConfig)
                                                                                                              (From
                                                                                                                 'V5
                                                                                                               :> (Description
                                                                                                                     ""
                                                                                                                   :> (ZUser
                                                                                                                       :> (Summary
                                                                                                                             "Put config for mlsMigration"
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("mlsMigration"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (Feature
                                                                                                                                                                        MlsMigrationConfig)
                                                                                                                                                                   :> Put
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           MlsMigrationConfig))))))))))))))))
                                                                                                      :<|> ((Named
                                                                                                               '("get",
                                                                                                                 EnforceFileDownloadLocationConfig)
                                                                                                               (From
                                                                                                                  'V5
                                                                                                                :> (Description
                                                                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                    :> (ZUser
                                                                                                                        :> (Summary
                                                                                                                              "Get config for enforceFileDownloadLocation"
                                                                                                                            :> (CanThrow
                                                                                                                                  OperationDenied
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                EnforceFileDownloadLocationConfig))))))))))))
                                                                                                             :<|> Named
                                                                                                                    '("put",
                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                    (From
                                                                                                                       'V5
                                                                                                                     :> (Description
                                                                                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                         :> (ZUser
                                                                                                                             :> (Summary
                                                                                                                                   "Put config for enforceFileDownloadLocation"
                                                                                                                                 :> (CanThrow
                                                                                                                                       OperationDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> (CanThrow
                                                                                                                                                   TeamFeatureError
                                                                                                                                                 :> (CanThrowMany
                                                                                                                                                       '[]
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> ("enforceFileDownloadLocation"
                                                                                                                                                                     :> (ReqBody
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (Feature
                                                                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                                                                         :> Put
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get",
                                                                                                                      LimitedEventFanoutConfig)
                                                                                                                    (From
                                                                                                                       'V5
                                                                                                                     :> (Description
                                                                                                                           ""
                                                                                                                         :> (ZUser
                                                                                                                             :> (Summary
                                                                                                                                   "Get config for limitedEventFanout"
                                                                                                                                 :> (CanThrow
                                                                                                                                       OperationDenied
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("limitedEventFanout"
                                                                                                                                                             :> Get
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     LimitedEventFanoutConfig))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-all-feature-configs-for-user"
                                                                                                                          (Summary
                                                                                                                             "Gets feature configs for a user"
                                                                                                                           :> (Description
                                                                                                                                 "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                               :> (DescriptionOAuthScope
                                                                                                                                     'ReadFeatureConfigs
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> Get
                                                                                                                                                            '[JSON]
                                                                                                                                                            AllTeamFeatures))))))))
                                                                                                                        :<|> (Named
                                                                                                                                "get-all-feature-configs-for-team"
                                                                                                                                (Summary
                                                                                                                                   "Gets feature configs for a team"
                                                                                                                                 :> (Description
                                                                                                                                       "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                                     :> (CanThrow
                                                                                                                                           'NotATeamMember
                                                                                                                                         :> (CanThrow
                                                                                                                                               OperationDenied
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'TeamNotFound
                                                                                                                                                 :> (ZLocalUser
                                                                                                                                                     :> ("teams"
                                                                                                                                                         :> (Capture
                                                                                                                                                               "tid"
                                                                                                                                                               TeamId
                                                                                                                                                             :> ("features"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      AllTeamFeatures)))))))))
                                                                                                                              :<|> ((Named
                                                                                                                                       '("get-deprecated",
                                                                                                                                         SearchVisibilityAvailableConfig)
                                                                                                                                       (ZUser
                                                                                                                                        :> (Summary
                                                                                                                                              "[deprecated] Get config for searchVisibility"
                                                                                                                                            :> (Until
                                                                                                                                                  'V2
                                                                                                                                                :> (Description
                                                                                                                                                      "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'NotATeamMember
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              OperationDenied
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("search-visibility"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        SearchVisibilityAvailableConfig))))))))))))
                                                                                                                                     :<|> (Named
                                                                                                                                             '("put-deprecated",
                                                                                                                                               SearchVisibilityAvailableConfig)
                                                                                                                                             (ZUser
                                                                                                                                              :> (Summary
                                                                                                                                                    "[deprecated] Get config for searchVisibility"
                                                                                                                                                  :> (Until
                                                                                                                                                        'V2
                                                                                                                                                      :> (Description
                                                                                                                                                            "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'NotATeamMember
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    OperationDenied
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            TeamFeatureError
                                                                                                                                                                          :> ("teams"
                                                                                                                                                                              :> (Capture
                                                                                                                                                                                    "tid"
                                                                                                                                                                                    TeamId
                                                                                                                                                                                  :> ("features"
                                                                                                                                                                                      :> ("search-visibility"
                                                                                                                                                                                          :> (ReqBody
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (Feature
                                                                                                                                                                                                   SearchVisibilityAvailableConfig)
                                                                                                                                                                                              :> Put
                                                                                                                                                                                                   '[JSON]
                                                                                                                                                                                                   (LockableFeature
                                                                                                                                                                                                      SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                                           :<|> (Named
                                                                                                                                                   '("get-deprecated",
                                                                                                                                                     ValidateSAMLEmailsConfig)
                                                                                                                                                   (ZUser
                                                                                                                                                    :> (Summary
                                                                                                                                                          "[deprecated] Get config for validateSAMLemails"
                                                                                                                                                        :> (Until
                                                                                                                                                              'V2
                                                                                                                                                            :> (Description
                                                                                                                                                                  "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          OperationDenied
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                            :> ("teams"
                                                                                                                                                                                :> (Capture
                                                                                                                                                                                      "tid"
                                                                                                                                                                                      TeamId
                                                                                                                                                                                    :> ("features"
                                                                                                                                                                                        :> ("validate-saml-emails"
                                                                                                                                                                                            :> Get
                                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                                    ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                                 :<|> Named
                                                                                                                                                        '("get-deprecated",
                                                                                                                                                          DigitalSignaturesConfig)
                                                                                                                                                        (ZUser
                                                                                                                                                         :> (Summary
                                                                                                                                                               "[deprecated] Get config for digitalSignatures"
                                                                                                                                                             :> (Until
                                                                                                                                                                   'V2
                                                                                                                                                                 :> (Description
                                                                                                                                                                       "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("teams"
                                                                                                                                                                                     :> (Capture
                                                                                                                                                                                           "tid"
                                                                                                                                                                                           TeamId
                                                                                                                                                                                         :> ("features"
                                                                                                                                                                                             :> ("digital-signatures"
                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                         DigitalSignaturesConfig)))))))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              LegalholdConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature legalhold"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("legalhold"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     LegalholdConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    SSOConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature sso"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("sso"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           SSOConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          SearchVisibilityAvailableConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("searchVisibility"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 SearchVisibilityAvailableConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                ValidateSAMLEmailsConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("validateSAMLemails"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      DigitalSignaturesConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("digitalSignatures"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             DigitalSignaturesConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            AppLockConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature appLock"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("appLock"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   AppLockConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  FileSharingConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("fileSharing"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         FileSharingConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        ClassifiedDomainsConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("classifiedDomains"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               ClassifiedDomainsConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              ConferenceCallingConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("conferenceCalling"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     ConferenceCallingConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    SelfDeletingMessagesConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("selfDeletingMessages"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        '("get-config",
                                                                                                                                                                                                          GuestLinksConfig)
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                 GuestLinksConfig))))))))))
                                                                                                                                                                                                      :<|> (Named
                                                                                                                                                                                                              '("get-config",
                                                                                                                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                              (Summary
                                                                                                                                                                                                                 "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                               :> (Until
                                                                                                                                                                                                                     'V2
                                                                                                                                                                                                                   :> (Description
                                                                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                       :> (ZUser
                                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                               :> Get
                                                                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                                                                       SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                            :<|> Named
                                                                                                                                                                                                                   '("get-config",
                                                                                                                                                                                                                     MLSConfig)
                                                                                                                                                                                                                   (Summary
                                                                                                                                                                                                                      "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                                    :> (Until
                                                                                                                                                                                                                          'V2
                                                                                                                                                                                                                        :> (Description
                                                                                                                                                                                                                              "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                            :> (ZUser
                                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                                                                            :> ("feature-configs"
                                                                                                                                                                                                                                                :> ("mls"
                                                                                                                                                                                                                                                    :> Get
                                                                                                                                                                                                                                                         '[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 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", DigitalSignaturesConfig) ServerT
  (Description ""
   :> (ZUser
       :> (Summary "Get config for digitalSignatures"
           :> (CanThrow OperationDenied
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow 'TeamNotFound
                       :> ("teams"
                           :> (Capture "tid" TeamId
                               :> ("features"
                                   :> ("digitalSignatures"
                                       :> Get
                                            '[JSON]
                                            (LockableFeature DigitalSignaturesConfig)))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Description ""
            :> (ZUser
                :> (Summary "Get config for digitalSignatures"
                    :> (CanThrow OperationDenied
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features"
                                            :> ("digitalSignatures"
                                                :> Get
                                                     '[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]))
UserId
-> TeamId
-> Sem
     '[Error (Tagged OperationDenied ()),
       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]
     (LockableFeature DigitalSignaturesConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member TeamFeatureStore r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member TeamStore r) =>
UserId -> TeamId -> Sem r (LockableFeature cfg)
getFeature
    API
  (Named
     '("get", DigitalSignaturesConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for digitalSignatures"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("digitalSignatures"
                                          :> Get
                                               '[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
         '("get", AppLockConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for appLock"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("appLock"
                                              :> Get
                                                   '[JSON] (LockableFeature AppLockConfig)))))))))))
       :<|> Named
              '("put", AppLockConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for appLock"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("appLock"
                                                           :> (ReqBody
                                                                 '[JSON] (Feature AppLockConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       AppLockConfig)))))))))))))))
      :<|> ((Named
               '("get", FileSharingConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for fileSharing"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("fileSharing"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            FileSharingConfig)))))))))))
             :<|> Named
                    '("put", FileSharingConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for fileSharing"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("fileSharing"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature FileSharingConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             FileSharingConfig)))))))))))))))
            :<|> (Named
                    '("get", ClassifiedDomainsConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Get config for classifiedDomains"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("classifiedDomains"
                                                         :> Get
                                                              '[JSON]
                                                              (LockableFeature
                                                                 ClassifiedDomainsConfig)))))))))))
                  :<|> ((Named
                           '("get", ConferenceCallingConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for conferenceCalling"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("conferenceCalling"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        ConferenceCallingConfig)))))))))))
                         :<|> Named
                                '("put", ConferenceCallingConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for conferenceCalling"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("conferenceCalling"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      ConferenceCallingConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         ConferenceCallingConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", SelfDeletingMessagesConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for selfDeletingMessages"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("selfDeletingMessages"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              SelfDeletingMessagesConfig)))))))))))
                               :<|> Named
                                      '("put", SelfDeletingMessagesConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for selfDeletingMessages"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("selfDeletingMessages"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            SelfDeletingMessagesConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               SelfDeletingMessagesConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", GuestLinksConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for conversationGuestLinks"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("conversationGuestLinks"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    GuestLinksConfig)))))))))))
                                     :<|> Named
                                            '("put", GuestLinksConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Put config for conversationGuestLinks"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("conversationGuestLinks"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  GuestLinksConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     GuestLinksConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", SndFactorPasswordChallengeConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary
                                                        "Get config for sndFactorPasswordChallenge"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("sndFactorPasswordChallenge"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          SndFactorPasswordChallengeConfig)))))))))))
                                           :<|> Named
                                                  '("put", SndFactorPasswordChallengeConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for sndFactorPasswordChallenge"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           SndFactorPasswordChallengeConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", MLSConfig)
                                                   (From 'V5
                                                    :> (Description ""
                                                        :> (ZUser
                                                            :> (Summary "Get config for mls"
                                                                :> (CanThrow OperationDenied
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mls"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    MLSConfig))))))))))))
                                                 :<|> Named
                                                        '("put", MLSConfig)
                                                        (From 'V5
                                                         :> (Description ""
                                                             :> (ZUser
                                                                 :> (Summary "Put config for mls"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("mls"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (Feature
                                                                                                                  MLSConfig)
                                                                                                             :> Put
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     MLSConfig))))))))))))))))
                                                :<|> ((Named
                                                         '("get",
                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for exposeInvitationURLsToTeamAdmin"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                       :<|> Named
                                                              '("put",
                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for exposeInvitationURLsToTeamAdmin"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get",
                                                                 SearchVisibilityInboundConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for searchVisibilityInbound"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("searchVisibilityInbound"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            SearchVisibilityInboundConfig)))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      SearchVisibilityInboundConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for searchVisibilityInbound"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("searchVisibilityInbound"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          SearchVisibilityInboundConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             SearchVisibilityInboundConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get",
                                                                       OutlookCalIntegrationConfig)
                                                                     (Description ""
                                                                      :> (ZUser
                                                                          :> (Summary
                                                                                "Get config for outlookCalIntegration"
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("outlookCalIntegration"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  OutlookCalIntegrationConfig)))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            OutlookCalIntegrationConfig)
                                                                          (Description ""
                                                                           :> (ZUser
                                                                               :> (Summary
                                                                                     "Put config for outlookCalIntegration"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("outlookCalIntegration"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                OutlookCalIntegrationConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   OutlookCalIntegrationConfig)))))))))))))))
                                                                  :<|> (Named
                                                                          '("get", MlsE2EIdConfig)
                                                                          (From 'V5
                                                                           :> (Description ""
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Get config for mlsE2EId"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("mlsE2EId"
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           MlsE2EIdConfig))))))))))))
                                                                        :<|> (Named
                                                                                "put-MlsE2EIdConfig@v5"
                                                                                (From 'V5
                                                                                 :> (Until 'V6
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Put config for mlsE2EId"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("mlsE2EId"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (Feature
                                                                                                                                          MlsE2EIdConfig)
                                                                                                                                     :> Put
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             MlsE2EIdConfig)))))))))))))))
                                                                              :<|> (Named
                                                                                      '("put",
                                                                                        MlsE2EIdConfig)
                                                                                      (From 'V6
                                                                                       :> (Description
                                                                                             ""
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Put config for mlsE2EId"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("mlsE2EId"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (Feature
                                                                                                                                                MlsE2EIdConfig)
                                                                                                                                           :> Put
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   MlsE2EIdConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("get",
                                                                                               MlsMigrationConfig)
                                                                                             (From
                                                                                                'V5
                                                                                              :> (Description
                                                                                                    ""
                                                                                                  :> (ZUser
                                                                                                      :> (Summary
                                                                                                            "Get config for mlsMigration"
                                                                                                          :> (CanThrow
                                                                                                                OperationDenied
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mlsMigration"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              MlsMigrationConfig))))))))))))
                                                                                           :<|> Named
                                                                                                  '("put",
                                                                                                    MlsMigrationConfig)
                                                                                                  (From
                                                                                                     'V5
                                                                                                   :> (Description
                                                                                                         ""
                                                                                                       :> (ZUser
                                                                                                           :> (Summary
                                                                                                                 "Put config for mlsMigration"
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("mlsMigration"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (Feature
                                                                                                                                                            MlsMigrationConfig)
                                                                                                                                                       :> Put
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               MlsMigrationConfig))))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("get",
                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                   (From
                                                                                                      'V5
                                                                                                    :> (Description
                                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                        :> (ZUser
                                                                                                            :> (Summary
                                                                                                                  "Get config for enforceFileDownloadLocation"
                                                                                                                :> (CanThrow
                                                                                                                      OperationDenied
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("enforceFileDownloadLocation"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    EnforceFileDownloadLocationConfig))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("put",
                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                        (From
                                                                                                           'V5
                                                                                                         :> (Description
                                                                                                               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                             :> (ZUser
                                                                                                                 :> (Summary
                                                                                                                       "Put config for enforceFileDownloadLocation"
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("enforceFileDownloadLocation"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (Feature
                                                                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                                                                             :> Put
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get",
                                                                                                          LimitedEventFanoutConfig)
                                                                                                        (From
                                                                                                           'V5
                                                                                                         :> (Description
                                                                                                               ""
                                                                                                             :> (ZUser
                                                                                                                 :> (Summary
                                                                                                                       "Get config for limitedEventFanout"
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("limitedEventFanout"
                                                                                                                                                 :> Get
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         LimitedEventFanoutConfig))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-all-feature-configs-for-user"
                                                                                                              (Summary
                                                                                                                 "Gets feature configs for a user"
                                                                                                               :> (Description
                                                                                                                     "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                         'ReadFeatureConfigs
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> Get
                                                                                                                                                '[JSON]
                                                                                                                                                AllTeamFeatures))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-all-feature-configs-for-team"
                                                                                                                    (Summary
                                                                                                                       "Gets feature configs for a team"
                                                                                                                     :> (Description
                                                                                                                           "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   OperationDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          AllTeamFeatures)))))))))
                                                                                                                  :<|> ((Named
                                                                                                                           '("get-deprecated",
                                                                                                                             SearchVisibilityAvailableConfig)
                                                                                                                           (ZUser
                                                                                                                            :> (Summary
                                                                                                                                  "[deprecated] Get config for searchVisibility"
                                                                                                                                :> (Until
                                                                                                                                      'V2
                                                                                                                                    :> (Description
                                                                                                                                          "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                        :> (CanThrow
                                                                                                                                              'NotATeamMember
                                                                                                                                            :> (CanThrow
                                                                                                                                                  OperationDenied
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("search-visibility"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            SearchVisibilityAvailableConfig))))))))))))
                                                                                                                         :<|> (Named
                                                                                                                                 '("put-deprecated",
                                                                                                                                   SearchVisibilityAvailableConfig)
                                                                                                                                 (ZUser
                                                                                                                                  :> (Summary
                                                                                                                                        "[deprecated] Get config for searchVisibility"
                                                                                                                                      :> (Until
                                                                                                                                            'V2
                                                                                                                                          :> (Description
                                                                                                                                                "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'NotATeamMember
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        OperationDenied
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> ("teams"
                                                                                                                                                                  :> (Capture
                                                                                                                                                                        "tid"
                                                                                                                                                                        TeamId
                                                                                                                                                                      :> ("features"
                                                                                                                                                                          :> ("search-visibility"
                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (Feature
                                                                                                                                                                                       SearchVisibilityAvailableConfig)
                                                                                                                                                                                  :> Put
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                          SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                               :<|> (Named
                                                                                                                                       '("get-deprecated",
                                                                                                                                         ValidateSAMLEmailsConfig)
                                                                                                                                       (ZUser
                                                                                                                                        :> (Summary
                                                                                                                                              "[deprecated] Get config for validateSAMLemails"
                                                                                                                                            :> (Until
                                                                                                                                                  'V2
                                                                                                                                                :> (Description
                                                                                                                                                      "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'NotATeamMember
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              OperationDenied
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("validate-saml-emails"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                     :<|> Named
                                                                                                                                            '("get-deprecated",
                                                                                                                                              DigitalSignaturesConfig)
                                                                                                                                            (ZUser
                                                                                                                                             :> (Summary
                                                                                                                                                   "[deprecated] Get config for digitalSignatures"
                                                                                                                                                 :> (Until
                                                                                                                                                       'V2
                                                                                                                                                     :> (Description
                                                                                                                                                           "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("teams"
                                                                                                                                                                         :> (Capture
                                                                                                                                                                               "tid"
                                                                                                                                                                               TeamId
                                                                                                                                                                             :> ("features"
                                                                                                                                                                                 :> ("digital-signatures"
                                                                                                                                                                                     :> Get
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             DigitalSignaturesConfig)))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  LegalholdConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature legalhold"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("legalhold"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         LegalholdConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        SSOConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature sso"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("sso"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               SSOConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              SearchVisibilityAvailableConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("searchVisibility"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     SearchVisibilityAvailableConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    ValidateSAMLEmailsConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("validateSAMLemails"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          DigitalSignaturesConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("digitalSignatures"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 DigitalSignaturesConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                AppLockConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature appLock"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("appLock"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       AppLockConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      FileSharingConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("fileSharing"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             FileSharingConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            ClassifiedDomainsConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("classifiedDomains"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   ClassifiedDomainsConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  ConferenceCallingConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("conferenceCalling"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         ConferenceCallingConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        SelfDeletingMessagesConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("selfDeletingMessages"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              GuestLinksConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     GuestLinksConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                :<|> Named
                                                                                                                                                                                                       '("get-config",
                                                                                                                                                                                                         MLSConfig)
                                                                                                                                                                                                       (Summary
                                                                                                                                                                                                          "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                        :> (Until
                                                                                                                                                                                                              'V2
                                                                                                                                                                                                            :> (Description
                                                                                                                                                                                                                  "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                :> (ZUser
                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                                                                :> ("feature-configs"
                                                                                                                                                                                                                                    :> ("mls"
                                                                                                                                                                                                                                        :> Get
                                                                                                                                                                                                                                             '[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
        '("get", DigitalSignaturesConfig)
        (Description ""
         :> (ZUser
             :> (Summary "Get config for digitalSignatures"
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> ("digitalSignatures"
                                             :> Get
                                                  '[JSON]
                                                  (LockableFeature
                                                     DigitalSignaturesConfig)))))))))))
      :<|> ((Named
               '("get", AppLockConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for appLock"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("appLock"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature AppLockConfig)))))))))))
             :<|> Named
                    '("put", AppLockConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for appLock"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("appLock"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature AppLockConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             AppLockConfig)))))))))))))))
            :<|> ((Named
                     '("get", FileSharingConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for fileSharing"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("fileSharing"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  FileSharingConfig)))))))))))
                   :<|> Named
                          '("put", FileSharingConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for fileSharing"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("fileSharing"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                FileSharingConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   FileSharingConfig)))))))))))))))
                  :<|> (Named
                          '("get", ClassifiedDomainsConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Get config for classifiedDomains"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("classifiedDomains"
                                                               :> Get
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       ClassifiedDomainsConfig)))))))))))
                        :<|> ((Named
                                 '("get", ConferenceCallingConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for conferenceCalling"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("conferenceCalling"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              ConferenceCallingConfig)))))))))))
                               :<|> Named
                                      '("put", ConferenceCallingConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for conferenceCalling"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("conferenceCalling"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            ConferenceCallingConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               ConferenceCallingConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", SelfDeletingMessagesConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for selfDeletingMessages"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("selfDeletingMessages"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    SelfDeletingMessagesConfig)))))))))))
                                     :<|> Named
                                            '("put", SelfDeletingMessagesConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Put config for selfDeletingMessages"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("selfDeletingMessages"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  SelfDeletingMessagesConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     SelfDeletingMessagesConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", GuestLinksConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary
                                                        "Get config for conversationGuestLinks"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("conversationGuestLinks"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          GuestLinksConfig)))))))))))
                                           :<|> Named
                                                  '("put", GuestLinksConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for conversationGuestLinks"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("conversationGuestLinks"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        GuestLinksConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           GuestLinksConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", SndFactorPasswordChallengeConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for sndFactorPasswordChallenge"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("sndFactorPasswordChallenge"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                SndFactorPasswordChallengeConfig)))))))))))
                                                 :<|> Named
                                                        '("put", SndFactorPasswordChallengeConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for sndFactorPasswordChallenge"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              SndFactorPasswordChallengeConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 SndFactorPasswordChallengeConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", MLSConfig)
                                                         (From 'V5
                                                          :> (Description ""
                                                              :> (ZUser
                                                                  :> (Summary "Get config for mls"
                                                                      :> (CanThrow OperationDenied
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mls"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          MLSConfig))))))))))))
                                                       :<|> Named
                                                              '("put", MLSConfig)
                                                              (From 'V5
                                                               :> (Description ""
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Put config for mls"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("mls"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (Feature
                                                                                                                        MLSConfig)
                                                                                                                   :> Put
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           MLSConfig))))))))))))))))
                                                      :<|> ((Named
                                                               '("get",
                                                                 ExposeInvitationURLsToTeamAdminConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for exposeInvitationURLsToTeamAdmin"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for exposeInvitationURLsToTeamAdmin"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get",
                                                                       SearchVisibilityInboundConfig)
                                                                     (Description ""
                                                                      :> (ZUser
                                                                          :> (Summary
                                                                                "Get config for searchVisibilityInbound"
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("searchVisibilityInbound"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  SearchVisibilityInboundConfig)))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            SearchVisibilityInboundConfig)
                                                                          (Description ""
                                                                           :> (ZUser
                                                                               :> (Summary
                                                                                     "Put config for searchVisibilityInbound"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("searchVisibilityInbound"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                SearchVisibilityInboundConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   SearchVisibilityInboundConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             OutlookCalIntegrationConfig)
                                                                           (Description ""
                                                                            :> (ZUser
                                                                                :> (Summary
                                                                                      "Get config for outlookCalIntegration"
                                                                                    :> (CanThrow
                                                                                          OperationDenied
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("teams"
                                                                                                    :> (Capture
                                                                                                          "tid"
                                                                                                          TeamId
                                                                                                        :> ("features"
                                                                                                            :> ("outlookCalIntegration"
                                                                                                                :> Get
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        OutlookCalIntegrationConfig)))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  OutlookCalIntegrationConfig)
                                                                                (Description ""
                                                                                 :> (ZUser
                                                                                     :> (Summary
                                                                                           "Put config for outlookCalIntegration"
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> (CanThrow
                                                                                                           TeamFeatureError
                                                                                                         :> (CanThrowMany
                                                                                                               '[]
                                                                                                             :> ("teams"
                                                                                                                 :> (Capture
                                                                                                                       "tid"
                                                                                                                       TeamId
                                                                                                                     :> ("features"
                                                                                                                         :> ("outlookCalIntegration"
                                                                                                                             :> (ReqBody
                                                                                                                                   '[JSON]
                                                                                                                                   (Feature
                                                                                                                                      OutlookCalIntegrationConfig)
                                                                                                                                 :> Put
                                                                                                                                      '[JSON]
                                                                                                                                      (LockableFeature
                                                                                                                                         OutlookCalIntegrationConfig)))))))))))))))
                                                                        :<|> (Named
                                                                                '("get",
                                                                                  MlsE2EIdConfig)
                                                                                (From 'V5
                                                                                 :> (Description ""
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Get config for mlsE2EId"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("mlsE2EId"
                                                                                                                         :> Get
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 MlsE2EIdConfig))))))))))))
                                                                              :<|> (Named
                                                                                      "put-MlsE2EIdConfig@v5"
                                                                                      (From 'V5
                                                                                       :> (Until 'V6
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Put config for mlsE2EId"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("mlsE2EId"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (Feature
                                                                                                                                                MlsE2EIdConfig)
                                                                                                                                           :> Put
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   MlsE2EIdConfig)))))))))))))))
                                                                                    :<|> (Named
                                                                                            '("put",
                                                                                              MlsE2EIdConfig)
                                                                                            (From
                                                                                               'V6
                                                                                             :> (Description
                                                                                                   ""
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Put config for mlsE2EId"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("mlsE2EId"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (Feature
                                                                                                                                                      MlsE2EIdConfig)
                                                                                                                                                 :> Put
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MlsE2EIdConfig)))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("get",
                                                                                                     MlsMigrationConfig)
                                                                                                   (From
                                                                                                      'V5
                                                                                                    :> (Description
                                                                                                          ""
                                                                                                        :> (ZUser
                                                                                                            :> (Summary
                                                                                                                  "Get config for mlsMigration"
                                                                                                                :> (CanThrow
                                                                                                                      OperationDenied
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("mlsMigration"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    MlsMigrationConfig))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("put",
                                                                                                          MlsMigrationConfig)
                                                                                                        (From
                                                                                                           'V5
                                                                                                         :> (Description
                                                                                                               ""
                                                                                                             :> (ZUser
                                                                                                                 :> (Summary
                                                                                                                       "Put config for mlsMigration"
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("mlsMigration"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (Feature
                                                                                                                                                                  MlsMigrationConfig)
                                                                                                                                                             :> Put
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     MlsMigrationConfig))))))))))))))))
                                                                                                :<|> ((Named
                                                                                                         '("get",
                                                                                                           EnforceFileDownloadLocationConfig)
                                                                                                         (From
                                                                                                            'V5
                                                                                                          :> (Description
                                                                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                              :> (ZUser
                                                                                                                  :> (Summary
                                                                                                                        "Get config for enforceFileDownloadLocation"
                                                                                                                      :> (CanThrow
                                                                                                                            OperationDenied
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          EnforceFileDownloadLocationConfig))))))))))))
                                                                                                       :<|> Named
                                                                                                              '("put",
                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                              (From
                                                                                                                 'V5
                                                                                                               :> (Description
                                                                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                                   :> (ZUser
                                                                                                                       :> (Summary
                                                                                                                             "Put config for enforceFileDownloadLocation"
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> (CanThrow
                                                                                                                                             TeamFeatureError
                                                                                                                                           :> (CanThrowMany
                                                                                                                                                 '[]
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> ("enforceFileDownloadLocation"
                                                                                                                                                               :> (ReqBody
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (Feature
                                                                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                                                                   :> Put
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get",
                                                                                                                LimitedEventFanoutConfig)
                                                                                                              (From
                                                                                                                 'V5
                                                                                                               :> (Description
                                                                                                                     ""
                                                                                                                   :> (ZUser
                                                                                                                       :> (Summary
                                                                                                                             "Get config for limitedEventFanout"
                                                                                                                           :> (CanThrow
                                                                                                                                 OperationDenied
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("limitedEventFanout"
                                                                                                                                                       :> Get
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               LimitedEventFanoutConfig))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-all-feature-configs-for-user"
                                                                                                                    (Summary
                                                                                                                       "Gets feature configs for a user"
                                                                                                                     :> (Description
                                                                                                                           "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                         :> (DescriptionOAuthScope
                                                                                                                               'ReadFeatureConfigs
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> Get
                                                                                                                                                      '[JSON]
                                                                                                                                                      AllTeamFeatures))))))))
                                                                                                                  :<|> (Named
                                                                                                                          "get-all-feature-configs-for-team"
                                                                                                                          (Summary
                                                                                                                             "Gets feature configs for a team"
                                                                                                                           :> (Description
                                                                                                                                 "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                               :> (CanThrow
                                                                                                                                     'NotATeamMember
                                                                                                                                   :> (CanThrow
                                                                                                                                         OperationDenied
                                                                                                                                       :> (CanThrow
                                                                                                                                             'TeamNotFound
                                                                                                                                           :> (ZLocalUser
                                                                                                                                               :> ("teams"
                                                                                                                                                   :> (Capture
                                                                                                                                                         "tid"
                                                                                                                                                         TeamId
                                                                                                                                                       :> ("features"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                AllTeamFeatures)))))))))
                                                                                                                        :<|> ((Named
                                                                                                                                 '("get-deprecated",
                                                                                                                                   SearchVisibilityAvailableConfig)
                                                                                                                                 (ZUser
                                                                                                                                  :> (Summary
                                                                                                                                        "[deprecated] Get config for searchVisibility"
                                                                                                                                      :> (Until
                                                                                                                                            'V2
                                                                                                                                          :> (Description
                                                                                                                                                "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'NotATeamMember
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        OperationDenied
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("search-visibility"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  SearchVisibilityAvailableConfig))))))))))))
                                                                                                                               :<|> (Named
                                                                                                                                       '("put-deprecated",
                                                                                                                                         SearchVisibilityAvailableConfig)
                                                                                                                                       (ZUser
                                                                                                                                        :> (Summary
                                                                                                                                              "[deprecated] Get config for searchVisibility"
                                                                                                                                            :> (Until
                                                                                                                                                  'V2
                                                                                                                                                :> (Description
                                                                                                                                                      "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'NotATeamMember
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              OperationDenied
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      TeamFeatureError
                                                                                                                                                                    :> ("teams"
                                                                                                                                                                        :> (Capture
                                                                                                                                                                              "tid"
                                                                                                                                                                              TeamId
                                                                                                                                                                            :> ("features"
                                                                                                                                                                                :> ("search-visibility"
                                                                                                                                                                                    :> (ReqBody
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (Feature
                                                                                                                                                                                             SearchVisibilityAvailableConfig)
                                                                                                                                                                                        :> Put
                                                                                                                                                                                             '[JSON]
                                                                                                                                                                                             (LockableFeature
                                                                                                                                                                                                SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                                     :<|> (Named
                                                                                                                                             '("get-deprecated",
                                                                                                                                               ValidateSAMLEmailsConfig)
                                                                                                                                             (ZUser
                                                                                                                                              :> (Summary
                                                                                                                                                    "[deprecated] Get config for validateSAMLemails"
                                                                                                                                                  :> (Until
                                                                                                                                                        'V2
                                                                                                                                                      :> (Description
                                                                                                                                                            "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'NotATeamMember
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    OperationDenied
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                      :> ("teams"
                                                                                                                                                                          :> (Capture
                                                                                                                                                                                "tid"
                                                                                                                                                                                TeamId
                                                                                                                                                                              :> ("features"
                                                                                                                                                                                  :> ("validate-saml-emails"
                                                                                                                                                                                      :> Get
                                                                                                                                                                                           '[JSON]
                                                                                                                                                                                           (LockableFeature
                                                                                                                                                                                              ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                           :<|> Named
                                                                                                                                                  '("get-deprecated",
                                                                                                                                                    DigitalSignaturesConfig)
                                                                                                                                                  (ZUser
                                                                                                                                                   :> (Summary
                                                                                                                                                         "[deprecated] Get config for digitalSignatures"
                                                                                                                                                       :> (Until
                                                                                                                                                             'V2
                                                                                                                                                           :> (Description
                                                                                                                                                                 "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("teams"
                                                                                                                                                                               :> (Capture
                                                                                                                                                                                     "tid"
                                                                                                                                                                                     TeamId
                                                                                                                                                                                   :> ("features"
                                                                                                                                                                                       :> ("digital-signatures"
                                                                                                                                                                                           :> Get
                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                   DigitalSignaturesConfig)))))))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        LegalholdConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature legalhold"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("legalhold"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               LegalholdConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              SSOConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature sso"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("sso"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     SSOConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    SearchVisibilityAvailableConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("searchVisibility"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           SearchVisibilityAvailableConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          ValidateSAMLEmailsConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("validateSAMLemails"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                DigitalSignaturesConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("digitalSignatures"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       DigitalSignaturesConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      AppLockConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature appLock"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("appLock"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             AppLockConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            FileSharingConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("fileSharing"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   FileSharingConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  ClassifiedDomainsConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("classifiedDomains"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         ClassifiedDomainsConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        ConferenceCallingConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("conferenceCalling"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               ConferenceCallingConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              SelfDeletingMessagesConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("selfDeletingMessages"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    GuestLinksConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           GuestLinksConfig))))))))))
                                                                                                                                                                                                :<|> (Named
                                                                                                                                                                                                        '("get-config",
                                                                                                                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                        (Summary
                                                                                                                                                                                                           "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                         :> (Until
                                                                                                                                                                                                               'V2
                                                                                                                                                                                                             :> (Description
                                                                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                 :> (ZUser
                                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                                               OperationDenied
                                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                         :> Get
                                                                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                                                                 SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                      :<|> Named
                                                                                                                                                                                                             '("get-config",
                                                                                                                                                                                                               MLSConfig)
                                                                                                                                                                                                             (Summary
                                                                                                                                                                                                                "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                              :> (Until
                                                                                                                                                                                                                    'V2
                                                                                                                                                                                                                  :> (Description
                                                                                                                                                                                                                        "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                      :> (ZUser
                                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                                                                      :> ("feature-configs"
                                                                                                                                                                                                                                          :> ("mls"
                                                                                                                                                                                                                                              :> Get
                                                                                                                                                                                                                                                   '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     '("get", AppLockConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for appLock"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("appLock"
                                          :> Get '[JSON] (LockableFeature AppLockConfig)))))))))))
   :<|> Named
          '("put", AppLockConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for appLock"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("appLock"
                                                       :> (ReqBody '[JSON] (Feature AppLockConfig)
                                                           :> Put
                                                                '[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
     '("get", AppLockConfig)
     (Description (FeatureAPIDesc AppLockConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol "Get config for " (FeatureSymbol AppLockConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol AppLockConfig
                                          :> Get '[JSON] (LockableFeature AppLockConfig)))))))))))
   :<|> Named
          '("put", AppLockConfig)
          (Description (FeatureAPIDesc AppLockConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol "Put config for " (FeatureSymbol AppLockConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors AppLockConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol AppLockConfig
                                                       :> (ReqBody '[JSON] (Feature AppLockConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", AppLockConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for appLock"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("appLock"
                                          :> Get '[JSON] (LockableFeature AppLockConfig)))))))))))
   :<|> Named
          '("put", AppLockConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for appLock"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("appLock"
                                                       :> (ReqBody '[JSON] (Feature AppLockConfig)
                                                           :> Put
                                                                '[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
         '("get", FileSharingConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for fileSharing"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("fileSharing"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature FileSharingConfig)))))))))))
       :<|> Named
              '("put", FileSharingConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for fileSharing"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("fileSharing"
                                                           :> (ReqBody
                                                                 '[JSON] (Feature FileSharingConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       FileSharingConfig)))))))))))))))
      :<|> (Named
              '("get", ClassifiedDomainsConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Get config for classifiedDomains"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> ("teams"
                                       :> (Capture "tid" TeamId
                                           :> ("features"
                                               :> ("classifiedDomains"
                                                   :> Get
                                                        '[JSON]
                                                        (LockableFeature
                                                           ClassifiedDomainsConfig)))))))))))
            :<|> ((Named
                     '("get", ConferenceCallingConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for conferenceCalling"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("conferenceCalling"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  ConferenceCallingConfig)))))))))))
                   :<|> Named
                          '("put", ConferenceCallingConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for conferenceCalling"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("conferenceCalling"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                ConferenceCallingConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   ConferenceCallingConfig)))))))))))))))
                  :<|> ((Named
                           '("get", SelfDeletingMessagesConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for selfDeletingMessages"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("selfDeletingMessages"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        SelfDeletingMessagesConfig)))))))))))
                         :<|> Named
                                '("put", SelfDeletingMessagesConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for selfDeletingMessages"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("selfDeletingMessages"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      SelfDeletingMessagesConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         SelfDeletingMessagesConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", GuestLinksConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for conversationGuestLinks"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("conversationGuestLinks"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              GuestLinksConfig)))))))))))
                               :<|> Named
                                      '("put", GuestLinksConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for conversationGuestLinks"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("conversationGuestLinks"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            GuestLinksConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               GuestLinksConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", SndFactorPasswordChallengeConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for sndFactorPasswordChallenge"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("sndFactorPasswordChallenge"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    SndFactorPasswordChallengeConfig)))))))))))
                                     :<|> Named
                                            '("put", SndFactorPasswordChallengeConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary
                                                       "Put config for sndFactorPasswordChallenge"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     SndFactorPasswordChallengeConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", MLSConfig)
                                             (From 'V5
                                              :> (Description ""
                                                  :> (ZUser
                                                      :> (Summary "Get config for mls"
                                                          :> (CanThrow OperationDenied
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mls"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              MLSConfig))))))))))))
                                           :<|> Named
                                                  '("put", MLSConfig)
                                                  (From 'V5
                                                   :> (Description ""
                                                       :> (ZUser
                                                           :> (Summary "Put config for mls"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("mls"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (Feature
                                                                                                            MLSConfig)
                                                                                                       :> Put
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               MLSConfig))))))))))))))))
                                          :<|> ((Named
                                                   '("get", ExposeInvitationURLsToTeamAdminConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for exposeInvitationURLsToTeamAdmin"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                 :<|> Named
                                                        '("put",
                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for exposeInvitationURLsToTeamAdmin"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", SearchVisibilityInboundConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for searchVisibilityInbound"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("searchVisibilityInbound"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      SearchVisibilityInboundConfig)))))))))))
                                                       :<|> Named
                                                              '("put",
                                                                SearchVisibilityInboundConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for searchVisibilityInbound"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("searchVisibilityInbound"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    SearchVisibilityInboundConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       SearchVisibilityInboundConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get", OutlookCalIntegrationConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for outlookCalIntegration"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("outlookCalIntegration"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            OutlookCalIntegrationConfig)))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      OutlookCalIntegrationConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for outlookCalIntegration"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("outlookCalIntegration"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          OutlookCalIntegrationConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             OutlookCalIntegrationConfig)))))))))))))))
                                                            :<|> (Named
                                                                    '("get", MlsE2EIdConfig)
                                                                    (From 'V5
                                                                     :> (Description ""
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Get config for mlsE2EId"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("mlsE2EId"
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     MlsE2EIdConfig))))))))))))
                                                                  :<|> (Named
                                                                          "put-MlsE2EIdConfig@v5"
                                                                          (From 'V5
                                                                           :> (Until 'V6
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Put config for mlsE2EId"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("mlsE2EId"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (Feature
                                                                                                                                    MlsE2EIdConfig)
                                                                                                                               :> Put
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       MlsE2EIdConfig)))))))))))))))
                                                                        :<|> (Named
                                                                                '("put",
                                                                                  MlsE2EIdConfig)
                                                                                (From 'V6
                                                                                 :> (Description ""
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Put config for mlsE2EId"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("mlsE2EId"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (Feature
                                                                                                                                          MlsE2EIdConfig)
                                                                                                                                     :> Put
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             MlsE2EIdConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("get",
                                                                                         MlsMigrationConfig)
                                                                                       (From 'V5
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (ZUser
                                                                                                :> (Summary
                                                                                                      "Get config for mlsMigration"
                                                                                                    :> (CanThrow
                                                                                                          OperationDenied
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mlsMigration"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        MlsMigrationConfig))))))))))))
                                                                                     :<|> Named
                                                                                            '("put",
                                                                                              MlsMigrationConfig)
                                                                                            (From
                                                                                               'V5
                                                                                             :> (Description
                                                                                                   ""
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Put config for mlsMigration"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("mlsMigration"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (Feature
                                                                                                                                                      MlsMigrationConfig)
                                                                                                                                                 :> Put
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MlsMigrationConfig))))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("get",
                                                                                               EnforceFileDownloadLocationConfig)
                                                                                             (From
                                                                                                'V5
                                                                                              :> (Description
                                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                  :> (ZUser
                                                                                                      :> (Summary
                                                                                                            "Get config for enforceFileDownloadLocation"
                                                                                                          :> (CanThrow
                                                                                                                OperationDenied
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              EnforceFileDownloadLocationConfig))))))))))))
                                                                                           :<|> Named
                                                                                                  '("put",
                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                  (From
                                                                                                     'V5
                                                                                                   :> (Description
                                                                                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                       :> (ZUser
                                                                                                           :> (Summary
                                                                                                                 "Put config for enforceFileDownloadLocation"
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("enforceFileDownloadLocation"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (Feature
                                                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                                                       :> Put
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get",
                                                                                                    LimitedEventFanoutConfig)
                                                                                                  (From
                                                                                                     'V5
                                                                                                   :> (Description
                                                                                                         ""
                                                                                                       :> (ZUser
                                                                                                           :> (Summary
                                                                                                                 "Get config for limitedEventFanout"
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                           :> Get
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   LimitedEventFanoutConfig))))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-all-feature-configs-for-user"
                                                                                                        (Summary
                                                                                                           "Gets feature configs for a user"
                                                                                                         :> (Description
                                                                                                               "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                             :> (DescriptionOAuthScope
                                                                                                                   'ReadFeatureConfigs
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> Get
                                                                                                                                          '[JSON]
                                                                                                                                          AllTeamFeatures))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-all-feature-configs-for-team"
                                                                                                              (Summary
                                                                                                                 "Gets feature configs for a team"
                                                                                                               :> (Description
                                                                                                                     "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             OperationDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    AllTeamFeatures)))))))))
                                                                                                            :<|> ((Named
                                                                                                                     '("get-deprecated",
                                                                                                                       SearchVisibilityAvailableConfig)
                                                                                                                     (ZUser
                                                                                                                      :> (Summary
                                                                                                                            "[deprecated] Get config for searchVisibility"
                                                                                                                          :> (Until
                                                                                                                                'V2
                                                                                                                              :> (Description
                                                                                                                                    "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                  :> (CanThrow
                                                                                                                                        'NotATeamMember
                                                                                                                                      :> (CanThrow
                                                                                                                                            OperationDenied
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("search-visibility"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      SearchVisibilityAvailableConfig))))))))))))
                                                                                                                   :<|> (Named
                                                                                                                           '("put-deprecated",
                                                                                                                             SearchVisibilityAvailableConfig)
                                                                                                                           (ZUser
                                                                                                                            :> (Summary
                                                                                                                                  "[deprecated] Get config for searchVisibility"
                                                                                                                                :> (Until
                                                                                                                                      'V2
                                                                                                                                    :> (Description
                                                                                                                                          "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                        :> (CanThrow
                                                                                                                                              'NotATeamMember
                                                                                                                                            :> (CanThrow
                                                                                                                                                  OperationDenied
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> ("teams"
                                                                                                                                                            :> (Capture
                                                                                                                                                                  "tid"
                                                                                                                                                                  TeamId
                                                                                                                                                                :> ("features"
                                                                                                                                                                    :> ("search-visibility"
                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (Feature
                                                                                                                                                                                 SearchVisibilityAvailableConfig)
                                                                                                                                                                            :> Put
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                    SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                         :<|> (Named
                                                                                                                                 '("get-deprecated",
                                                                                                                                   ValidateSAMLEmailsConfig)
                                                                                                                                 (ZUser
                                                                                                                                  :> (Summary
                                                                                                                                        "[deprecated] Get config for validateSAMLemails"
                                                                                                                                      :> (Until
                                                                                                                                            'V2
                                                                                                                                          :> (Description
                                                                                                                                                "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'NotATeamMember
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        OperationDenied
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("validate-saml-emails"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  ValidateSAMLEmailsConfig))))))))))))
                                                                                                                               :<|> Named
                                                                                                                                      '("get-deprecated",
                                                                                                                                        DigitalSignaturesConfig)
                                                                                                                                      (ZUser
                                                                                                                                       :> (Summary
                                                                                                                                             "[deprecated] Get config for digitalSignatures"
                                                                                                                                           :> (Until
                                                                                                                                                 'V2
                                                                                                                                               :> (Description
                                                                                                                                                     "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("teams"
                                                                                                                                                                   :> (Capture
                                                                                                                                                                         "tid"
                                                                                                                                                                         TeamId
                                                                                                                                                                       :> ("features"
                                                                                                                                                                           :> ("digital-signatures"
                                                                                                                                                                               :> Get
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       DigitalSignaturesConfig)))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            LegalholdConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature legalhold"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("legalhold"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   LegalholdConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  SSOConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature sso"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("sso"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         SSOConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        SearchVisibilityAvailableConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("searchVisibility"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               SearchVisibilityAvailableConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              ValidateSAMLEmailsConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("validateSAMLemails"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     ValidateSAMLEmailsConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    DigitalSignaturesConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("digitalSignatures"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           DigitalSignaturesConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          AppLockConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature appLock"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("appLock"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 AppLockConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                FileSharingConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("fileSharing"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       FileSharingConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      ClassifiedDomainsConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("classifiedDomains"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             ClassifiedDomainsConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            ConferenceCallingConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("conferenceCalling"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   ConferenceCallingConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  SelfDeletingMessagesConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("selfDeletingMessages"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        GuestLinksConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               GuestLinksConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              SndFactorPasswordChallengeConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                          :<|> Named
                                                                                                                                                                                                 '("get-config",
                                                                                                                                                                                                   MLSConfig)
                                                                                                                                                                                                 (Summary
                                                                                                                                                                                                    "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                  :> (Until
                                                                                                                                                                                                        'V2
                                                                                                                                                                                                      :> (Description
                                                                                                                                                                                                            "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                          :> (ZUser
                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                                          :> ("feature-configs"
                                                                                                                                                                                                                              :> ("mls"
                                                                                                                                                                                                                                  :> Get
                                                                                                                                                                                                                                       '[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
         '("get", AppLockConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for appLock"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("appLock"
                                              :> Get
                                                   '[JSON] (LockableFeature AppLockConfig)))))))))))
       :<|> Named
              '("put", AppLockConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for appLock"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("appLock"
                                                           :> (ReqBody
                                                                 '[JSON] (Feature AppLockConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       AppLockConfig)))))))))))))))
      :<|> ((Named
               '("get", FileSharingConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for fileSharing"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("fileSharing"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            FileSharingConfig)))))))))))
             :<|> Named
                    '("put", FileSharingConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for fileSharing"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("fileSharing"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature FileSharingConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             FileSharingConfig)))))))))))))))
            :<|> (Named
                    '("get", ClassifiedDomainsConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Get config for classifiedDomains"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("classifiedDomains"
                                                         :> Get
                                                              '[JSON]
                                                              (LockableFeature
                                                                 ClassifiedDomainsConfig)))))))))))
                  :<|> ((Named
                           '("get", ConferenceCallingConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for conferenceCalling"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("conferenceCalling"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        ConferenceCallingConfig)))))))))))
                         :<|> Named
                                '("put", ConferenceCallingConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for conferenceCalling"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("conferenceCalling"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      ConferenceCallingConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         ConferenceCallingConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", SelfDeletingMessagesConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for selfDeletingMessages"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("selfDeletingMessages"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              SelfDeletingMessagesConfig)))))))))))
                               :<|> Named
                                      '("put", SelfDeletingMessagesConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for selfDeletingMessages"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("selfDeletingMessages"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            SelfDeletingMessagesConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               SelfDeletingMessagesConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", GuestLinksConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for conversationGuestLinks"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("conversationGuestLinks"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    GuestLinksConfig)))))))))))
                                     :<|> Named
                                            '("put", GuestLinksConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Put config for conversationGuestLinks"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("conversationGuestLinks"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  GuestLinksConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     GuestLinksConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", SndFactorPasswordChallengeConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary
                                                        "Get config for sndFactorPasswordChallenge"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("sndFactorPasswordChallenge"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          SndFactorPasswordChallengeConfig)))))))))))
                                           :<|> Named
                                                  '("put", SndFactorPasswordChallengeConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for sndFactorPasswordChallenge"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           SndFactorPasswordChallengeConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", MLSConfig)
                                                   (From 'V5
                                                    :> (Description ""
                                                        :> (ZUser
                                                            :> (Summary "Get config for mls"
                                                                :> (CanThrow OperationDenied
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mls"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    MLSConfig))))))))))))
                                                 :<|> Named
                                                        '("put", MLSConfig)
                                                        (From 'V5
                                                         :> (Description ""
                                                             :> (ZUser
                                                                 :> (Summary "Put config for mls"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("mls"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (Feature
                                                                                                                  MLSConfig)
                                                                                                             :> Put
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     MLSConfig))))))))))))))))
                                                :<|> ((Named
                                                         '("get",
                                                           ExposeInvitationURLsToTeamAdminConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for exposeInvitationURLsToTeamAdmin"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("exposeInvitationURLsToTeamAdmin"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                       :<|> Named
                                                              '("put",
                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for exposeInvitationURLsToTeamAdmin"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get",
                                                                 SearchVisibilityInboundConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for searchVisibilityInbound"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("searchVisibilityInbound"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            SearchVisibilityInboundConfig)))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      SearchVisibilityInboundConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for searchVisibilityInbound"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("searchVisibilityInbound"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          SearchVisibilityInboundConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             SearchVisibilityInboundConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get",
                                                                       OutlookCalIntegrationConfig)
                                                                     (Description ""
                                                                      :> (ZUser
                                                                          :> (Summary
                                                                                "Get config for outlookCalIntegration"
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("teams"
                                                                                              :> (Capture
                                                                                                    "tid"
                                                                                                    TeamId
                                                                                                  :> ("features"
                                                                                                      :> ("outlookCalIntegration"
                                                                                                          :> Get
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  OutlookCalIntegrationConfig)))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            OutlookCalIntegrationConfig)
                                                                          (Description ""
                                                                           :> (ZUser
                                                                               :> (Summary
                                                                                     "Put config for outlookCalIntegration"
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 'TeamNotFound
                                                                                               :> (CanThrow
                                                                                                     TeamFeatureError
                                                                                                   :> (CanThrowMany
                                                                                                         '[]
                                                                                                       :> ("teams"
                                                                                                           :> (Capture
                                                                                                                 "tid"
                                                                                                                 TeamId
                                                                                                               :> ("features"
                                                                                                                   :> ("outlookCalIntegration"
                                                                                                                       :> (ReqBody
                                                                                                                             '[JSON]
                                                                                                                             (Feature
                                                                                                                                OutlookCalIntegrationConfig)
                                                                                                                           :> Put
                                                                                                                                '[JSON]
                                                                                                                                (LockableFeature
                                                                                                                                   OutlookCalIntegrationConfig)))))))))))))))
                                                                  :<|> (Named
                                                                          '("get", MlsE2EIdConfig)
                                                                          (From 'V5
                                                                           :> (Description ""
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Get config for mlsE2EId"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("mlsE2EId"
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           MlsE2EIdConfig))))))))))))
                                                                        :<|> (Named
                                                                                "put-MlsE2EIdConfig@v5"
                                                                                (From 'V5
                                                                                 :> (Until 'V6
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Put config for mlsE2EId"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("mlsE2EId"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (Feature
                                                                                                                                          MlsE2EIdConfig)
                                                                                                                                     :> Put
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             MlsE2EIdConfig)))))))))))))))
                                                                              :<|> (Named
                                                                                      '("put",
                                                                                        MlsE2EIdConfig)
                                                                                      (From 'V6
                                                                                       :> (Description
                                                                                             ""
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Put config for mlsE2EId"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("mlsE2EId"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (Feature
                                                                                                                                                MlsE2EIdConfig)
                                                                                                                                           :> Put
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   MlsE2EIdConfig)))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("get",
                                                                                               MlsMigrationConfig)
                                                                                             (From
                                                                                                'V5
                                                                                              :> (Description
                                                                                                    ""
                                                                                                  :> (ZUser
                                                                                                      :> (Summary
                                                                                                            "Get config for mlsMigration"
                                                                                                          :> (CanThrow
                                                                                                                OperationDenied
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("mlsMigration"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              MlsMigrationConfig))))))))))))
                                                                                           :<|> Named
                                                                                                  '("put",
                                                                                                    MlsMigrationConfig)
                                                                                                  (From
                                                                                                     'V5
                                                                                                   :> (Description
                                                                                                         ""
                                                                                                       :> (ZUser
                                                                                                           :> (Summary
                                                                                                                 "Put config for mlsMigration"
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("mlsMigration"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (Feature
                                                                                                                                                            MlsMigrationConfig)
                                                                                                                                                       :> Put
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               MlsMigrationConfig))))))))))))))))
                                                                                          :<|> ((Named
                                                                                                   '("get",
                                                                                                     EnforceFileDownloadLocationConfig)
                                                                                                   (From
                                                                                                      'V5
                                                                                                    :> (Description
                                                                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                        :> (ZUser
                                                                                                            :> (Summary
                                                                                                                  "Get config for enforceFileDownloadLocation"
                                                                                                                :> (CanThrow
                                                                                                                      OperationDenied
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("enforceFileDownloadLocation"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    EnforceFileDownloadLocationConfig))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("put",
                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                        (From
                                                                                                           'V5
                                                                                                         :> (Description
                                                                                                               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                             :> (ZUser
                                                                                                                 :> (Summary
                                                                                                                       "Put config for enforceFileDownloadLocation"
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> (CanThrow
                                                                                                                                       TeamFeatureError
                                                                                                                                     :> (CanThrowMany
                                                                                                                                           '[]
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> ("enforceFileDownloadLocation"
                                                                                                                                                         :> (ReqBody
                                                                                                                                                               '[JSON]
                                                                                                                                                               (Feature
                                                                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                                                                             :> Put
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get",
                                                                                                          LimitedEventFanoutConfig)
                                                                                                        (From
                                                                                                           'V5
                                                                                                         :> (Description
                                                                                                               ""
                                                                                                             :> (ZUser
                                                                                                                 :> (Summary
                                                                                                                       "Get config for limitedEventFanout"
                                                                                                                     :> (CanThrow
                                                                                                                           OperationDenied
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("limitedEventFanout"
                                                                                                                                                 :> Get
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         LimitedEventFanoutConfig))))))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-all-feature-configs-for-user"
                                                                                                              (Summary
                                                                                                                 "Gets feature configs for a user"
                                                                                                               :> (Description
                                                                                                                     "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                                   :> (DescriptionOAuthScope
                                                                                                                         'ReadFeatureConfigs
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> Get
                                                                                                                                                '[JSON]
                                                                                                                                                AllTeamFeatures))))))))
                                                                                                            :<|> (Named
                                                                                                                    "get-all-feature-configs-for-team"
                                                                                                                    (Summary
                                                                                                                       "Gets feature configs for a team"
                                                                                                                     :> (Description
                                                                                                                           "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                         :> (CanThrow
                                                                                                                               'NotATeamMember
                                                                                                                             :> (CanThrow
                                                                                                                                   OperationDenied
                                                                                                                                 :> (CanThrow
                                                                                                                                       'TeamNotFound
                                                                                                                                     :> (ZLocalUser
                                                                                                                                         :> ("teams"
                                                                                                                                             :> (Capture
                                                                                                                                                   "tid"
                                                                                                                                                   TeamId
                                                                                                                                                 :> ("features"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          AllTeamFeatures)))))))))
                                                                                                                  :<|> ((Named
                                                                                                                           '("get-deprecated",
                                                                                                                             SearchVisibilityAvailableConfig)
                                                                                                                           (ZUser
                                                                                                                            :> (Summary
                                                                                                                                  "[deprecated] Get config for searchVisibility"
                                                                                                                                :> (Until
                                                                                                                                      'V2
                                                                                                                                    :> (Description
                                                                                                                                          "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                        :> (CanThrow
                                                                                                                                              'NotATeamMember
                                                                                                                                            :> (CanThrow
                                                                                                                                                  OperationDenied
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("search-visibility"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            SearchVisibilityAvailableConfig))))))))))))
                                                                                                                         :<|> (Named
                                                                                                                                 '("put-deprecated",
                                                                                                                                   SearchVisibilityAvailableConfig)
                                                                                                                                 (ZUser
                                                                                                                                  :> (Summary
                                                                                                                                        "[deprecated] Get config for searchVisibility"
                                                                                                                                      :> (Until
                                                                                                                                            'V2
                                                                                                                                          :> (Description
                                                                                                                                                "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'NotATeamMember
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        OperationDenied
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                TeamFeatureError
                                                                                                                                                              :> ("teams"
                                                                                                                                                                  :> (Capture
                                                                                                                                                                        "tid"
                                                                                                                                                                        TeamId
                                                                                                                                                                      :> ("features"
                                                                                                                                                                          :> ("search-visibility"
                                                                                                                                                                              :> (ReqBody
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (Feature
                                                                                                                                                                                       SearchVisibilityAvailableConfig)
                                                                                                                                                                                  :> Put
                                                                                                                                                                                       '[JSON]
                                                                                                                                                                                       (LockableFeature
                                                                                                                                                                                          SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                               :<|> (Named
                                                                                                                                       '("get-deprecated",
                                                                                                                                         ValidateSAMLEmailsConfig)
                                                                                                                                       (ZUser
                                                                                                                                        :> (Summary
                                                                                                                                              "[deprecated] Get config for validateSAMLemails"
                                                                                                                                            :> (Until
                                                                                                                                                  'V2
                                                                                                                                                :> (Description
                                                                                                                                                      "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'NotATeamMember
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              OperationDenied
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                :> ("teams"
                                                                                                                                                                    :> (Capture
                                                                                                                                                                          "tid"
                                                                                                                                                                          TeamId
                                                                                                                                                                        :> ("features"
                                                                                                                                                                            :> ("validate-saml-emails"
                                                                                                                                                                                :> Get
                                                                                                                                                                                     '[JSON]
                                                                                                                                                                                     (LockableFeature
                                                                                                                                                                                        ValidateSAMLEmailsConfig))))))))))))
                                                                                                                                     :<|> Named
                                                                                                                                            '("get-deprecated",
                                                                                                                                              DigitalSignaturesConfig)
                                                                                                                                            (ZUser
                                                                                                                                             :> (Summary
                                                                                                                                                   "[deprecated] Get config for digitalSignatures"
                                                                                                                                                 :> (Until
                                                                                                                                                       'V2
                                                                                                                                                     :> (Description
                                                                                                                                                           "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("teams"
                                                                                                                                                                         :> (Capture
                                                                                                                                                                               "tid"
                                                                                                                                                                               TeamId
                                                                                                                                                                             :> ("features"
                                                                                                                                                                                 :> ("digital-signatures"
                                                                                                                                                                                     :> Get
                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                             DigitalSignaturesConfig)))))))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  LegalholdConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature legalhold"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("legalhold"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         LegalholdConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        SSOConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature sso"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("sso"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               SSOConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              SearchVisibilityAvailableConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("searchVisibility"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     SearchVisibilityAvailableConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    ValidateSAMLEmailsConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("validateSAMLemails"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           ValidateSAMLEmailsConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          DigitalSignaturesConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("digitalSignatures"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 DigitalSignaturesConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                AppLockConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature appLock"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("appLock"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       AppLockConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      FileSharingConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("fileSharing"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             FileSharingConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            ClassifiedDomainsConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("classifiedDomains"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   ClassifiedDomainsConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  ConferenceCallingConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("conferenceCalling"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         ConferenceCallingConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        SelfDeletingMessagesConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("selfDeletingMessages"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              GuestLinksConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     GuestLinksConfig))))))))))
                                                                                                                                                                                          :<|> (Named
                                                                                                                                                                                                  '("get-config",
                                                                                                                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                                                                                                                                  (Summary
                                                                                                                                                                                                     "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                                   :> (Until
                                                                                                                                                                                                         'V2
                                                                                                                                                                                                       :> (Description
                                                                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                           :> (ZUser
                                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                                         OperationDenied
                                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                                   :> Get
                                                                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                                                                           SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                                :<|> Named
                                                                                                                                                                                                       '("get-config",
                                                                                                                                                                                                         MLSConfig)
                                                                                                                                                                                                       (Summary
                                                                                                                                                                                                          "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                        :> (Until
                                                                                                                                                                                                              'V2
                                                                                                                                                                                                            :> (Description
                                                                                                                                                                                                                  "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                                :> (ZUser
                                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                                              OperationDenied
                                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                                                                :> ("feature-configs"
                                                                                                                                                                                                                                    :> ("mls"
                                                                                                                                                                                                                                        :> Get
                                                                                                                                                                                                                                             '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     '("get", FileSharingConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for fileSharing"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("fileSharing"
                                          :> Get
                                               '[JSON] (LockableFeature FileSharingConfig)))))))))))
   :<|> Named
          '("put", FileSharingConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for fileSharing"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("fileSharing"
                                                       :> (ReqBody
                                                             '[JSON] (Feature FileSharingConfig)
                                                           :> Put
                                                                '[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
     '("get", FileSharingConfig)
     (Description (FeatureAPIDesc FileSharingConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol "Get config for " (FeatureSymbol FileSharingConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol FileSharingConfig
                                          :> Get
                                               '[JSON] (LockableFeature FileSharingConfig)))))))))))
   :<|> Named
          '("put", FileSharingConfig)
          (Description (FeatureAPIDesc FileSharingConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol "Put config for " (FeatureSymbol FileSharingConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors FileSharingConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol FileSharingConfig
                                                       :> (ReqBody
                                                             '[JSON] (Feature FileSharingConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", FileSharingConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for fileSharing"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("fileSharing"
                                          :> Get
                                               '[JSON] (LockableFeature FileSharingConfig)))))))))))
   :<|> Named
          '("put", FileSharingConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for fileSharing"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("fileSharing"
                                                       :> (ReqBody
                                                             '[JSON] (Feature FileSharingConfig)
                                                           :> Put
                                                                '[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
        '("get", ClassifiedDomainsConfig)
        (Description ""
         :> (ZUser
             :> (Summary "Get config for classifiedDomains"
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> ("classifiedDomains"
                                             :> Get
                                                  '[JSON]
                                                  (LockableFeature
                                                     ClassifiedDomainsConfig)))))))))))
      :<|> ((Named
               '("get", ConferenceCallingConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for conferenceCalling"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("conferenceCalling"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            ConferenceCallingConfig)))))))))))
             :<|> Named
                    '("put", ConferenceCallingConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for conferenceCalling"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("conferenceCalling"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          ConferenceCallingConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             ConferenceCallingConfig)))))))))))))))
            :<|> ((Named
                     '("get", SelfDeletingMessagesConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for selfDeletingMessages"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("selfDeletingMessages"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  SelfDeletingMessagesConfig)))))))))))
                   :<|> Named
                          '("put", SelfDeletingMessagesConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for selfDeletingMessages"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("selfDeletingMessages"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                SelfDeletingMessagesConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   SelfDeletingMessagesConfig)))))))))))))))
                  :<|> ((Named
                           '("get", GuestLinksConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for conversationGuestLinks"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("conversationGuestLinks"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        GuestLinksConfig)))))))))))
                         :<|> Named
                                '("put", GuestLinksConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for conversationGuestLinks"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("conversationGuestLinks"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      GuestLinksConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         GuestLinksConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", SndFactorPasswordChallengeConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for sndFactorPasswordChallenge"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("sndFactorPasswordChallenge"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              SndFactorPasswordChallengeConfig)))))))))))
                               :<|> Named
                                      '("put", SndFactorPasswordChallengeConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for sndFactorPasswordChallenge"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("sndFactorPasswordChallenge"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            SndFactorPasswordChallengeConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               SndFactorPasswordChallengeConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", MLSConfig)
                                       (From 'V5
                                        :> (Description ""
                                            :> (ZUser
                                                :> (Summary "Get config for mls"
                                                    :> (CanThrow OperationDenied
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("mls"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        MLSConfig))))))))))))
                                     :<|> Named
                                            '("put", MLSConfig)
                                            (From 'V5
                                             :> (Description ""
                                                 :> (ZUser
                                                     :> (Summary "Put config for mls"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("mls"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (Feature
                                                                                                      MLSConfig)
                                                                                                 :> Put
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         MLSConfig))))))))))))))))
                                    :<|> ((Named
                                             '("get", ExposeInvitationURLsToTeamAdminConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary
                                                        "Get config for exposeInvitationURLsToTeamAdmin"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                           :<|> Named
                                                  '("put", ExposeInvitationURLsToTeamAdminConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for exposeInvitationURLsToTeamAdmin"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("exposeInvitationURLsToTeamAdmin"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", SearchVisibilityInboundConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for searchVisibilityInbound"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("searchVisibilityInbound"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                SearchVisibilityInboundConfig)))))))))))
                                                 :<|> Named
                                                        '("put", SearchVisibilityInboundConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for searchVisibilityInbound"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("searchVisibilityInbound"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              SearchVisibilityInboundConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 SearchVisibilityInboundConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", OutlookCalIntegrationConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for outlookCalIntegration"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("outlookCalIntegration"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      OutlookCalIntegrationConfig)))))))))))
                                                       :<|> Named
                                                              '("put", OutlookCalIntegrationConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for outlookCalIntegration"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("outlookCalIntegration"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    OutlookCalIntegrationConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       OutlookCalIntegrationConfig)))))))))))))))
                                                      :<|> (Named
                                                              '("get", MlsE2EIdConfig)
                                                              (From 'V5
                                                               :> (Description ""
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Get config for mlsE2EId"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("mlsE2EId"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               MlsE2EIdConfig))))))))))))
                                                            :<|> (Named
                                                                    "put-MlsE2EIdConfig@v5"
                                                                    (From 'V5
                                                                     :> (Until 'V6
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Put config for mlsE2EId"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("mlsE2EId"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (Feature
                                                                                                                              MlsE2EIdConfig)
                                                                                                                         :> Put
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 MlsE2EIdConfig)))))))))))))))
                                                                  :<|> (Named
                                                                          '("put", MlsE2EIdConfig)
                                                                          (From 'V6
                                                                           :> (Description ""
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Put config for mlsE2EId"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("mlsE2EId"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (Feature
                                                                                                                                    MlsE2EIdConfig)
                                                                                                                               :> Put
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       MlsE2EIdConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get",
                                                                                   MlsMigrationConfig)
                                                                                 (From 'V5
                                                                                  :> (Description ""
                                                                                      :> (ZUser
                                                                                          :> (Summary
                                                                                                "Get config for mlsMigration"
                                                                                              :> (CanThrow
                                                                                                    OperationDenied
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mlsMigration"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  MlsMigrationConfig))))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        MlsMigrationConfig)
                                                                                      (From 'V5
                                                                                       :> (Description
                                                                                             ""
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Put config for mlsMigration"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("mlsMigration"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (Feature
                                                                                                                                                MlsMigrationConfig)
                                                                                                                                           :> Put
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   MlsMigrationConfig))))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("get",
                                                                                         EnforceFileDownloadLocationConfig)
                                                                                       (From 'V5
                                                                                        :> (Description
                                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                            :> (ZUser
                                                                                                :> (Summary
                                                                                                      "Get config for enforceFileDownloadLocation"
                                                                                                    :> (CanThrow
                                                                                                          OperationDenied
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        EnforceFileDownloadLocationConfig))))))))))))
                                                                                     :<|> Named
                                                                                            '("put",
                                                                                              EnforceFileDownloadLocationConfig)
                                                                                            (From
                                                                                               'V5
                                                                                             :> (Description
                                                                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Put config for enforceFileDownloadLocation"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("enforceFileDownloadLocation"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (Feature
                                                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                                                 :> Put
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                    :<|> (Named
                                                                                            '("get",
                                                                                              LimitedEventFanoutConfig)
                                                                                            (From
                                                                                               'V5
                                                                                             :> (Description
                                                                                                   ""
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Get config for limitedEventFanout"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("limitedEventFanout"
                                                                                                                                     :> Get
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             LimitedEventFanoutConfig))))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-all-feature-configs-for-user"
                                                                                                  (Summary
                                                                                                     "Gets feature configs for a user"
                                                                                                   :> (Description
                                                                                                         "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                       :> (DescriptionOAuthScope
                                                                                                             'ReadFeatureConfigs
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> Get
                                                                                                                                    '[JSON]
                                                                                                                                    AllTeamFeatures))))))))
                                                                                                :<|> (Named
                                                                                                        "get-all-feature-configs-for-team"
                                                                                                        (Summary
                                                                                                           "Gets feature configs for a team"
                                                                                                         :> (Description
                                                                                                               "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              AllTeamFeatures)))))))))
                                                                                                      :<|> ((Named
                                                                                                               '("get-deprecated",
                                                                                                                 SearchVisibilityAvailableConfig)
                                                                                                               (ZUser
                                                                                                                :> (Summary
                                                                                                                      "[deprecated] Get config for searchVisibility"
                                                                                                                    :> (Until
                                                                                                                          'V2
                                                                                                                        :> (Description
                                                                                                                              "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                            :> (CanThrow
                                                                                                                                  'NotATeamMember
                                                                                                                                :> (CanThrow
                                                                                                                                      OperationDenied
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("search-visibility"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                SearchVisibilityAvailableConfig))))))))))))
                                                                                                             :<|> (Named
                                                                                                                     '("put-deprecated",
                                                                                                                       SearchVisibilityAvailableConfig)
                                                                                                                     (ZUser
                                                                                                                      :> (Summary
                                                                                                                            "[deprecated] Get config for searchVisibility"
                                                                                                                          :> (Until
                                                                                                                                'V2
                                                                                                                              :> (Description
                                                                                                                                    "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                  :> (CanThrow
                                                                                                                                        'NotATeamMember
                                                                                                                                      :> (CanThrow
                                                                                                                                            OperationDenied
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> ("teams"
                                                                                                                                                      :> (Capture
                                                                                                                                                            "tid"
                                                                                                                                                            TeamId
                                                                                                                                                          :> ("features"
                                                                                                                                                              :> ("search-visibility"
                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (Feature
                                                                                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                                                                                      :> Put
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeature
                                                                                                                                                                              SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                   :<|> (Named
                                                                                                                           '("get-deprecated",
                                                                                                                             ValidateSAMLEmailsConfig)
                                                                                                                           (ZUser
                                                                                                                            :> (Summary
                                                                                                                                  "[deprecated] Get config for validateSAMLemails"
                                                                                                                                :> (Until
                                                                                                                                      'V2
                                                                                                                                    :> (Description
                                                                                                                                          "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                        :> (CanThrow
                                                                                                                                              'NotATeamMember
                                                                                                                                            :> (CanThrow
                                                                                                                                                  OperationDenied
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("validate-saml-emails"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            ValidateSAMLEmailsConfig))))))))))))
                                                                                                                         :<|> Named
                                                                                                                                '("get-deprecated",
                                                                                                                                  DigitalSignaturesConfig)
                                                                                                                                (ZUser
                                                                                                                                 :> (Summary
                                                                                                                                       "[deprecated] Get config for digitalSignatures"
                                                                                                                                     :> (Until
                                                                                                                                           'V2
                                                                                                                                         :> (Description
                                                                                                                                               "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("teams"
                                                                                                                                                             :> (Capture
                                                                                                                                                                   "tid"
                                                                                                                                                                   TeamId
                                                                                                                                                                 :> ("features"
                                                                                                                                                                     :> ("digital-signatures"
                                                                                                                                                                         :> Get
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 DigitalSignaturesConfig)))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      LegalholdConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature legalhold"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("legalhold"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             LegalholdConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            SSOConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature sso"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("sso"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   SSOConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  SearchVisibilityAvailableConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("searchVisibility"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         SearchVisibilityAvailableConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        ValidateSAMLEmailsConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("validateSAMLemails"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               ValidateSAMLEmailsConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              DigitalSignaturesConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("digitalSignatures"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     DigitalSignaturesConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    AppLockConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature appLock"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("appLock"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           AppLockConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          FileSharingConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("fileSharing"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 FileSharingConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                ClassifiedDomainsConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("classifiedDomains"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       ClassifiedDomainsConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      ConferenceCallingConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("conferenceCalling"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             ConferenceCallingConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            SelfDeletingMessagesConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("selfDeletingMessages"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  GuestLinksConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         GuestLinksConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                           '("get-config",
                                                                                                                                                                                             MLSConfig)
                                                                                                                                                                                           (Summary
                                                                                                                                                                                              "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                            :> (Until
                                                                                                                                                                                                  'V2
                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                    :> (ZUser
                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                    :> ("feature-configs"
                                                                                                                                                                                                                        :> ("mls"
                                                                                                                                                                                                                            :> Get
                                                                                                                                                                                                                                 '[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
         '("get", FileSharingConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for fileSharing"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("fileSharing"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature FileSharingConfig)))))))))))
       :<|> Named
              '("put", FileSharingConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for fileSharing"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("fileSharing"
                                                           :> (ReqBody
                                                                 '[JSON] (Feature FileSharingConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       FileSharingConfig)))))))))))))))
      :<|> (Named
              '("get", ClassifiedDomainsConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Get config for classifiedDomains"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> ("teams"
                                       :> (Capture "tid" TeamId
                                           :> ("features"
                                               :> ("classifiedDomains"
                                                   :> Get
                                                        '[JSON]
                                                        (LockableFeature
                                                           ClassifiedDomainsConfig)))))))))))
            :<|> ((Named
                     '("get", ConferenceCallingConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for conferenceCalling"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("conferenceCalling"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  ConferenceCallingConfig)))))))))))
                   :<|> Named
                          '("put", ConferenceCallingConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for conferenceCalling"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("conferenceCalling"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                ConferenceCallingConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   ConferenceCallingConfig)))))))))))))))
                  :<|> ((Named
                           '("get", SelfDeletingMessagesConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for selfDeletingMessages"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("selfDeletingMessages"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        SelfDeletingMessagesConfig)))))))))))
                         :<|> Named
                                '("put", SelfDeletingMessagesConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for selfDeletingMessages"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("selfDeletingMessages"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      SelfDeletingMessagesConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         SelfDeletingMessagesConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", GuestLinksConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for conversationGuestLinks"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("conversationGuestLinks"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              GuestLinksConfig)))))))))))
                               :<|> Named
                                      '("put", GuestLinksConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for conversationGuestLinks"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("conversationGuestLinks"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            GuestLinksConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               GuestLinksConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", SndFactorPasswordChallengeConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for sndFactorPasswordChallenge"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("sndFactorPasswordChallenge"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    SndFactorPasswordChallengeConfig)))))))))))
                                     :<|> Named
                                            '("put", SndFactorPasswordChallengeConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary
                                                       "Put config for sndFactorPasswordChallenge"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     SndFactorPasswordChallengeConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", MLSConfig)
                                             (From 'V5
                                              :> (Description ""
                                                  :> (ZUser
                                                      :> (Summary "Get config for mls"
                                                          :> (CanThrow OperationDenied
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mls"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              MLSConfig))))))))))))
                                           :<|> Named
                                                  '("put", MLSConfig)
                                                  (From 'V5
                                                   :> (Description ""
                                                       :> (ZUser
                                                           :> (Summary "Put config for mls"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("mls"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (Feature
                                                                                                            MLSConfig)
                                                                                                       :> Put
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               MLSConfig))))))))))))))))
                                          :<|> ((Named
                                                   '("get", ExposeInvitationURLsToTeamAdminConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for exposeInvitationURLsToTeamAdmin"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("exposeInvitationURLsToTeamAdmin"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                                 :<|> Named
                                                        '("put",
                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for exposeInvitationURLsToTeamAdmin"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("exposeInvitationURLsToTeamAdmin"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              ExposeInvitationURLsToTeamAdminConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", SearchVisibilityInboundConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for searchVisibilityInbound"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("searchVisibilityInbound"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      SearchVisibilityInboundConfig)))))))))))
                                                       :<|> Named
                                                              '("put",
                                                                SearchVisibilityInboundConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for searchVisibilityInbound"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("searchVisibilityInbound"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    SearchVisibilityInboundConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       SearchVisibilityInboundConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get", OutlookCalIntegrationConfig)
                                                               (Description ""
                                                                :> (ZUser
                                                                    :> (Summary
                                                                          "Get config for outlookCalIntegration"
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("teams"
                                                                                        :> (Capture
                                                                                              "tid"
                                                                                              TeamId
                                                                                            :> ("features"
                                                                                                :> ("outlookCalIntegration"
                                                                                                    :> Get
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            OutlookCalIntegrationConfig)))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      OutlookCalIntegrationConfig)
                                                                    (Description ""
                                                                     :> (ZUser
                                                                         :> (Summary
                                                                               "Put config for outlookCalIntegration"
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           'TeamNotFound
                                                                                         :> (CanThrow
                                                                                               TeamFeatureError
                                                                                             :> (CanThrowMany
                                                                                                   '[]
                                                                                                 :> ("teams"
                                                                                                     :> (Capture
                                                                                                           "tid"
                                                                                                           TeamId
                                                                                                         :> ("features"
                                                                                                             :> ("outlookCalIntegration"
                                                                                                                 :> (ReqBody
                                                                                                                       '[JSON]
                                                                                                                       (Feature
                                                                                                                          OutlookCalIntegrationConfig)
                                                                                                                     :> Put
                                                                                                                          '[JSON]
                                                                                                                          (LockableFeature
                                                                                                                             OutlookCalIntegrationConfig)))))))))))))))
                                                            :<|> (Named
                                                                    '("get", MlsE2EIdConfig)
                                                                    (From 'V5
                                                                     :> (Description ""
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Get config for mlsE2EId"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("mlsE2EId"
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     MlsE2EIdConfig))))))))))))
                                                                  :<|> (Named
                                                                          "put-MlsE2EIdConfig@v5"
                                                                          (From 'V5
                                                                           :> (Until 'V6
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Put config for mlsE2EId"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("mlsE2EId"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (Feature
                                                                                                                                    MlsE2EIdConfig)
                                                                                                                               :> Put
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       MlsE2EIdConfig)))))))))))))))
                                                                        :<|> (Named
                                                                                '("put",
                                                                                  MlsE2EIdConfig)
                                                                                (From 'V6
                                                                                 :> (Description ""
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Put config for mlsE2EId"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("mlsE2EId"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (Feature
                                                                                                                                          MlsE2EIdConfig)
                                                                                                                                     :> Put
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             MlsE2EIdConfig)))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("get",
                                                                                         MlsMigrationConfig)
                                                                                       (From 'V5
                                                                                        :> (Description
                                                                                              ""
                                                                                            :> (ZUser
                                                                                                :> (Summary
                                                                                                      "Get config for mlsMigration"
                                                                                                    :> (CanThrow
                                                                                                          OperationDenied
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("mlsMigration"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        MlsMigrationConfig))))))))))))
                                                                                     :<|> Named
                                                                                            '("put",
                                                                                              MlsMigrationConfig)
                                                                                            (From
                                                                                               'V5
                                                                                             :> (Description
                                                                                                   ""
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Put config for mlsMigration"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("mlsMigration"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (Feature
                                                                                                                                                      MlsMigrationConfig)
                                                                                                                                                 :> Put
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         MlsMigrationConfig))))))))))))))))
                                                                                    :<|> ((Named
                                                                                             '("get",
                                                                                               EnforceFileDownloadLocationConfig)
                                                                                             (From
                                                                                                'V5
                                                                                              :> (Description
                                                                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                  :> (ZUser
                                                                                                      :> (Summary
                                                                                                            "Get config for enforceFileDownloadLocation"
                                                                                                          :> (CanThrow
                                                                                                                OperationDenied
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("enforceFileDownloadLocation"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              EnforceFileDownloadLocationConfig))))))))))))
                                                                                           :<|> Named
                                                                                                  '("put",
                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                  (From
                                                                                                     'V5
                                                                                                   :> (Description
                                                                                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                       :> (ZUser
                                                                                                           :> (Summary
                                                                                                                 "Put config for enforceFileDownloadLocation"
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> (CanThrow
                                                                                                                                 TeamFeatureError
                                                                                                                               :> (CanThrowMany
                                                                                                                                     '[]
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> ("enforceFileDownloadLocation"
                                                                                                                                                   :> (ReqBody
                                                                                                                                                         '[JSON]
                                                                                                                                                         (Feature
                                                                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                                                                       :> Put
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get",
                                                                                                    LimitedEventFanoutConfig)
                                                                                                  (From
                                                                                                     'V5
                                                                                                   :> (Description
                                                                                                         ""
                                                                                                       :> (ZUser
                                                                                                           :> (Summary
                                                                                                                 "Get config for limitedEventFanout"
                                                                                                               :> (CanThrow
                                                                                                                     OperationDenied
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("limitedEventFanout"
                                                                                                                                           :> Get
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   LimitedEventFanoutConfig))))))))))))
                                                                                                :<|> (Named
                                                                                                        "get-all-feature-configs-for-user"
                                                                                                        (Summary
                                                                                                           "Gets feature configs for a user"
                                                                                                         :> (Description
                                                                                                               "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                             :> (DescriptionOAuthScope
                                                                                                                   'ReadFeatureConfigs
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> Get
                                                                                                                                          '[JSON]
                                                                                                                                          AllTeamFeatures))))))))
                                                                                                      :<|> (Named
                                                                                                              "get-all-feature-configs-for-team"
                                                                                                              (Summary
                                                                                                                 "Gets feature configs for a team"
                                                                                                               :> (Description
                                                                                                                     "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                                   :> (CanThrow
                                                                                                                         'NotATeamMember
                                                                                                                       :> (CanThrow
                                                                                                                             OperationDenied
                                                                                                                           :> (CanThrow
                                                                                                                                 'TeamNotFound
                                                                                                                               :> (ZLocalUser
                                                                                                                                   :> ("teams"
                                                                                                                                       :> (Capture
                                                                                                                                             "tid"
                                                                                                                                             TeamId
                                                                                                                                           :> ("features"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    AllTeamFeatures)))))))))
                                                                                                            :<|> ((Named
                                                                                                                     '("get-deprecated",
                                                                                                                       SearchVisibilityAvailableConfig)
                                                                                                                     (ZUser
                                                                                                                      :> (Summary
                                                                                                                            "[deprecated] Get config for searchVisibility"
                                                                                                                          :> (Until
                                                                                                                                'V2
                                                                                                                              :> (Description
                                                                                                                                    "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                  :> (CanThrow
                                                                                                                                        'NotATeamMember
                                                                                                                                      :> (CanThrow
                                                                                                                                            OperationDenied
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("search-visibility"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      SearchVisibilityAvailableConfig))))))))))))
                                                                                                                   :<|> (Named
                                                                                                                           '("put-deprecated",
                                                                                                                             SearchVisibilityAvailableConfig)
                                                                                                                           (ZUser
                                                                                                                            :> (Summary
                                                                                                                                  "[deprecated] Get config for searchVisibility"
                                                                                                                                :> (Until
                                                                                                                                      'V2
                                                                                                                                    :> (Description
                                                                                                                                          "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                        :> (CanThrow
                                                                                                                                              'NotATeamMember
                                                                                                                                            :> (CanThrow
                                                                                                                                                  OperationDenied
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          TeamFeatureError
                                                                                                                                                        :> ("teams"
                                                                                                                                                            :> (Capture
                                                                                                                                                                  "tid"
                                                                                                                                                                  TeamId
                                                                                                                                                                :> ("features"
                                                                                                                                                                    :> ("search-visibility"
                                                                                                                                                                        :> (ReqBody
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (Feature
                                                                                                                                                                                 SearchVisibilityAvailableConfig)
                                                                                                                                                                            :> Put
                                                                                                                                                                                 '[JSON]
                                                                                                                                                                                 (LockableFeature
                                                                                                                                                                                    SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                         :<|> (Named
                                                                                                                                 '("get-deprecated",
                                                                                                                                   ValidateSAMLEmailsConfig)
                                                                                                                                 (ZUser
                                                                                                                                  :> (Summary
                                                                                                                                        "[deprecated] Get config for validateSAMLemails"
                                                                                                                                      :> (Until
                                                                                                                                            'V2
                                                                                                                                          :> (Description
                                                                                                                                                "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'NotATeamMember
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        OperationDenied
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            'TeamNotFound
                                                                                                                                                          :> ("teams"
                                                                                                                                                              :> (Capture
                                                                                                                                                                    "tid"
                                                                                                                                                                    TeamId
                                                                                                                                                                  :> ("features"
                                                                                                                                                                      :> ("validate-saml-emails"
                                                                                                                                                                          :> Get
                                                                                                                                                                               '[JSON]
                                                                                                                                                                               (LockableFeature
                                                                                                                                                                                  ValidateSAMLEmailsConfig))))))))))))
                                                                                                                               :<|> Named
                                                                                                                                      '("get-deprecated",
                                                                                                                                        DigitalSignaturesConfig)
                                                                                                                                      (ZUser
                                                                                                                                       :> (Summary
                                                                                                                                             "[deprecated] Get config for digitalSignatures"
                                                                                                                                           :> (Until
                                                                                                                                                 'V2
                                                                                                                                               :> (Description
                                                                                                                                                     "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("teams"
                                                                                                                                                                   :> (Capture
                                                                                                                                                                         "tid"
                                                                                                                                                                         TeamId
                                                                                                                                                                       :> ("features"
                                                                                                                                                                           :> ("digital-signatures"
                                                                                                                                                                               :> Get
                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                       DigitalSignaturesConfig)))))))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            LegalholdConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature legalhold"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("legalhold"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   LegalholdConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  SSOConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature sso"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("sso"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         SSOConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        SearchVisibilityAvailableConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("searchVisibility"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               SearchVisibilityAvailableConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              ValidateSAMLEmailsConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("validateSAMLemails"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     ValidateSAMLEmailsConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    DigitalSignaturesConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("digitalSignatures"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           DigitalSignaturesConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          AppLockConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature appLock"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("appLock"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 AppLockConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                FileSharingConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("fileSharing"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       FileSharingConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      ClassifiedDomainsConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("classifiedDomains"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             ClassifiedDomainsConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            ConferenceCallingConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("conferenceCalling"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   ConferenceCallingConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  SelfDeletingMessagesConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("selfDeletingMessages"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        GuestLinksConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               GuestLinksConfig))))))))))
                                                                                                                                                                                    :<|> (Named
                                                                                                                                                                                            '("get-config",
                                                                                                                                                                                              SndFactorPasswordChallengeConfig)
                                                                                                                                                                                            (Summary
                                                                                                                                                                                               "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                             :> (Until
                                                                                                                                                                                                   'V2
                                                                                                                                                                                                 :> (Description
                                                                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                     :> (ZUser
                                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                                               'NotATeamMember
                                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                                   OperationDenied
                                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                             :> Get
                                                                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                                                                     SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                          :<|> Named
                                                                                                                                                                                                 '("get-config",
                                                                                                                                                                                                   MLSConfig)
                                                                                                                                                                                                 (Summary
                                                                                                                                                                                                    "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                                  :> (Until
                                                                                                                                                                                                        'V2
                                                                                                                                                                                                      :> (Description
                                                                                                                                                                                                            "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                          :> (ZUser
                                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                                        OperationDenied
                                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                                                                          :> ("feature-configs"
                                                                                                                                                                                                                              :> ("mls"
                                                                                                                                                                                                                                  :> Get
                                                                                                                                                                                                                                       '[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 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", ClassifiedDomainsConfig) ServerT
  (Description ""
   :> (ZUser
       :> (Summary "Get config for classifiedDomains"
           :> (CanThrow OperationDenied
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow 'TeamNotFound
                       :> ("teams"
                           :> (Capture "tid" TeamId
                               :> ("features"
                                   :> ("classifiedDomains"
                                       :> Get
                                            '[JSON]
                                            (LockableFeature ClassifiedDomainsConfig)))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Description ""
            :> (ZUser
                :> (Summary "Get config for classifiedDomains"
                    :> (CanThrow OperationDenied
                        :> (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]))
UserId
-> TeamId
-> Sem
     '[Error (Tagged OperationDenied ()),
       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]
     (LockableFeature ClassifiedDomainsConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member TeamFeatureStore r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member TeamStore r) =>
UserId -> TeamId -> Sem r (LockableFeature cfg)
getFeature
    API
  (Named
     '("get", ClassifiedDomainsConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for classifiedDomains"
              :> (CanThrow OperationDenied
                  :> (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
         '("get", ConferenceCallingConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for conferenceCalling"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("conferenceCalling"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      ConferenceCallingConfig)))))))))))
       :<|> Named
              '("put", ConferenceCallingConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for conferenceCalling"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("conferenceCalling"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature ConferenceCallingConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       ConferenceCallingConfig)))))))))))))))
      :<|> ((Named
               '("get", SelfDeletingMessagesConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for selfDeletingMessages"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("selfDeletingMessages"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            SelfDeletingMessagesConfig)))))))))))
             :<|> Named
                    '("put", SelfDeletingMessagesConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for selfDeletingMessages"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("selfDeletingMessages"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          SelfDeletingMessagesConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             SelfDeletingMessagesConfig)))))))))))))))
            :<|> ((Named
                     '("get", GuestLinksConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for conversationGuestLinks"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("conversationGuestLinks"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  GuestLinksConfig)))))))))))
                   :<|> Named
                          '("put", GuestLinksConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for conversationGuestLinks"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("conversationGuestLinks"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                GuestLinksConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   GuestLinksConfig)))))))))))))))
                  :<|> ((Named
                           '("get", SndFactorPasswordChallengeConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for sndFactorPasswordChallenge"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("sndFactorPasswordChallenge"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        SndFactorPasswordChallengeConfig)))))))))))
                         :<|> Named
                                '("put", SndFactorPasswordChallengeConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for sndFactorPasswordChallenge"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("sndFactorPasswordChallenge"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      SndFactorPasswordChallengeConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         SndFactorPasswordChallengeConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", MLSConfig)
                                 (From 'V5
                                  :> (Description ""
                                      :> (ZUser
                                          :> (Summary "Get config for mls"
                                              :> (CanThrow OperationDenied
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("mls"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  MLSConfig))))))))))))
                               :<|> Named
                                      '("put", MLSConfig)
                                      (From 'V5
                                       :> (Description ""
                                           :> (ZUser
                                               :> (Summary "Put config for mls"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("mls"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (Feature
                                                                                                MLSConfig)
                                                                                           :> Put
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   MLSConfig))))))))))))))))
                              :<|> ((Named
                                       '("get", ExposeInvitationURLsToTeamAdminConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary
                                                  "Get config for exposeInvitationURLsToTeamAdmin"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                     :<|> Named
                                            '("put", ExposeInvitationURLsToTeamAdminConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary
                                                       "Put config for exposeInvitationURLsToTeamAdmin"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", SearchVisibilityInboundConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary
                                                        "Get config for searchVisibilityInbound"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("searchVisibilityInbound"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          SearchVisibilityInboundConfig)))))))))))
                                           :<|> Named
                                                  '("put", SearchVisibilityInboundConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for searchVisibilityInbound"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("searchVisibilityInbound"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        SearchVisibilityInboundConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           SearchVisibilityInboundConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", OutlookCalIntegrationConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for outlookCalIntegration"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("outlookCalIntegration"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                OutlookCalIntegrationConfig)))))))))))
                                                 :<|> Named
                                                        '("put", OutlookCalIntegrationConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for outlookCalIntegration"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("outlookCalIntegration"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              OutlookCalIntegrationConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 OutlookCalIntegrationConfig)))))))))))))))
                                                :<|> (Named
                                                        '("get", MlsE2EIdConfig)
                                                        (From 'V5
                                                         :> (Description ""
                                                             :> (ZUser
                                                                 :> (Summary
                                                                       "Get config for mlsE2EId"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("mlsE2EId"
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         MlsE2EIdConfig))))))))))))
                                                      :<|> (Named
                                                              "put-MlsE2EIdConfig@v5"
                                                              (From 'V5
                                                               :> (Until 'V6
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Put config for mlsE2EId"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("mlsE2EId"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (Feature
                                                                                                                        MlsE2EIdConfig)
                                                                                                                   :> Put
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                            :<|> (Named
                                                                    '("put", MlsE2EIdConfig)
                                                                    (From 'V6
                                                                     :> (Description ""
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Put config for mlsE2EId"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("mlsE2EId"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (Feature
                                                                                                                              MlsE2EIdConfig)
                                                                                                                         :> Put
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 MlsE2EIdConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             MlsMigrationConfig)
                                                                           (From 'V5
                                                                            :> (Description ""
                                                                                :> (ZUser
                                                                                    :> (Summary
                                                                                          "Get config for mlsMigration"
                                                                                        :> (CanThrow
                                                                                              OperationDenied
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mlsMigration"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            MlsMigrationConfig))))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  MlsMigrationConfig)
                                                                                (From 'V5
                                                                                 :> (Description ""
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Put config for mlsMigration"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("mlsMigration"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (Feature
                                                                                                                                          MlsMigrationConfig)
                                                                                                                                     :> Put
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             MlsMigrationConfig))))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get",
                                                                                   EnforceFileDownloadLocationConfig)
                                                                                 (From 'V5
                                                                                  :> (Description
                                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                      :> (ZUser
                                                                                          :> (Summary
                                                                                                "Get config for enforceFileDownloadLocation"
                                                                                              :> (CanThrow
                                                                                                    OperationDenied
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  EnforceFileDownloadLocationConfig))))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        EnforceFileDownloadLocationConfig)
                                                                                      (From 'V5
                                                                                       :> (Description
                                                                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Put config for enforceFileDownloadLocation"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("enforceFileDownloadLocation"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (Feature
                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                           :> Put
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   EnforceFileDownloadLocationConfig))))))))))))))))
                                                                              :<|> (Named
                                                                                      '("get",
                                                                                        LimitedEventFanoutConfig)
                                                                                      (From 'V5
                                                                                       :> (Description
                                                                                             ""
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Get config for limitedEventFanout"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("limitedEventFanout"
                                                                                                                               :> Get
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       LimitedEventFanoutConfig))))))))))))
                                                                                    :<|> (Named
                                                                                            "get-all-feature-configs-for-user"
                                                                                            (Summary
                                                                                               "Gets feature configs for a user"
                                                                                             :> (Description
                                                                                                   "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                 :> (DescriptionOAuthScope
                                                                                                       'ReadFeatureConfigs
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> Get
                                                                                                                              '[JSON]
                                                                                                                              AllTeamFeatures))))))))
                                                                                          :<|> (Named
                                                                                                  "get-all-feature-configs-for-team"
                                                                                                  (Summary
                                                                                                     "Gets feature configs for a team"
                                                                                                   :> (Description
                                                                                                         "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        AllTeamFeatures)))))))))
                                                                                                :<|> ((Named
                                                                                                         '("get-deprecated",
                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                         (ZUser
                                                                                                          :> (Summary
                                                                                                                "[deprecated] Get config for searchVisibility"
                                                                                                              :> (Until
                                                                                                                    'V2
                                                                                                                  :> (Description
                                                                                                                        "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                OperationDenied
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("search-visibility"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          SearchVisibilityAvailableConfig))))))))))))
                                                                                                       :<|> (Named
                                                                                                               '("put-deprecated",
                                                                                                                 SearchVisibilityAvailableConfig)
                                                                                                               (ZUser
                                                                                                                :> (Summary
                                                                                                                      "[deprecated] Get config for searchVisibility"
                                                                                                                    :> (Until
                                                                                                                          'V2
                                                                                                                        :> (Description
                                                                                                                              "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                            :> (CanThrow
                                                                                                                                  'NotATeamMember
                                                                                                                                :> (CanThrow
                                                                                                                                      OperationDenied
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> ("teams"
                                                                                                                                                :> (Capture
                                                                                                                                                      "tid"
                                                                                                                                                      TeamId
                                                                                                                                                    :> ("features"
                                                                                                                                                        :> ("search-visibility"
                                                                                                                                                            :> (ReqBody
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (Feature
                                                                                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                                                                                :> Put
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeature
                                                                                                                                                                        SearchVisibilityAvailableConfig))))))))))))))
                                                                                                             :<|> (Named
                                                                                                                     '("get-deprecated",
                                                                                                                       ValidateSAMLEmailsConfig)
                                                                                                                     (ZUser
                                                                                                                      :> (Summary
                                                                                                                            "[deprecated] Get config for validateSAMLemails"
                                                                                                                          :> (Until
                                                                                                                                'V2
                                                                                                                              :> (Description
                                                                                                                                    "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                  :> (CanThrow
                                                                                                                                        'NotATeamMember
                                                                                                                                      :> (CanThrow
                                                                                                                                            OperationDenied
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("validate-saml-emails"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      ValidateSAMLEmailsConfig))))))))))))
                                                                                                                   :<|> Named
                                                                                                                          '("get-deprecated",
                                                                                                                            DigitalSignaturesConfig)
                                                                                                                          (ZUser
                                                                                                                           :> (Summary
                                                                                                                                 "[deprecated] Get config for digitalSignatures"
                                                                                                                               :> (Until
                                                                                                                                     'V2
                                                                                                                                   :> (Description
                                                                                                                                         "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("teams"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "tid"
                                                                                                                                                             TeamId
                                                                                                                                                           :> ("features"
                                                                                                                                                               :> ("digital-signatures"
                                                                                                                                                                   :> Get
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           DigitalSignaturesConfig)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                LegalholdConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature legalhold"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("legalhold"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       LegalholdConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      SSOConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature sso"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("sso"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             SSOConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            SearchVisibilityAvailableConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("searchVisibility"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   SearchVisibilityAvailableConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  ValidateSAMLEmailsConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("validateSAMLemails"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         ValidateSAMLEmailsConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        DigitalSignaturesConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("digitalSignatures"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               DigitalSignaturesConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              AppLockConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature appLock"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("appLock"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     AppLockConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    FileSharingConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("fileSharing"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           FileSharingConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          ClassifiedDomainsConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("classifiedDomains"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 ClassifiedDomainsConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                ConferenceCallingConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("conferenceCalling"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       ConferenceCallingConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      SelfDeletingMessagesConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("selfDeletingMessages"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            GuestLinksConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   GuestLinksConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                              :<|> Named
                                                                                                                                                                                     '("get-config",
                                                                                                                                                                                       MLSConfig)
                                                                                                                                                                                     (Summary
                                                                                                                                                                                        "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                      :> (Until
                                                                                                                                                                                            'V2
                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                              :> (ZUser
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                              :> ("feature-configs"
                                                                                                                                                                                                                  :> ("mls"
                                                                                                                                                                                                                      :> Get
                                                                                                                                                                                                                           '[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
        '("get", ClassifiedDomainsConfig)
        (Description ""
         :> (ZUser
             :> (Summary "Get config for classifiedDomains"
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> ("classifiedDomains"
                                             :> Get
                                                  '[JSON]
                                                  (LockableFeature
                                                     ClassifiedDomainsConfig)))))))))))
      :<|> ((Named
               '("get", ConferenceCallingConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for conferenceCalling"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("conferenceCalling"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            ConferenceCallingConfig)))))))))))
             :<|> Named
                    '("put", ConferenceCallingConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for conferenceCalling"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("conferenceCalling"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          ConferenceCallingConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             ConferenceCallingConfig)))))))))))))))
            :<|> ((Named
                     '("get", SelfDeletingMessagesConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for selfDeletingMessages"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("selfDeletingMessages"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  SelfDeletingMessagesConfig)))))))))))
                   :<|> Named
                          '("put", SelfDeletingMessagesConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for selfDeletingMessages"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("selfDeletingMessages"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                SelfDeletingMessagesConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   SelfDeletingMessagesConfig)))))))))))))))
                  :<|> ((Named
                           '("get", GuestLinksConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for conversationGuestLinks"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("conversationGuestLinks"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        GuestLinksConfig)))))))))))
                         :<|> Named
                                '("put", GuestLinksConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for conversationGuestLinks"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("conversationGuestLinks"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      GuestLinksConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         GuestLinksConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", SndFactorPasswordChallengeConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for sndFactorPasswordChallenge"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("sndFactorPasswordChallenge"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              SndFactorPasswordChallengeConfig)))))))))))
                               :<|> Named
                                      '("put", SndFactorPasswordChallengeConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for sndFactorPasswordChallenge"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("sndFactorPasswordChallenge"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            SndFactorPasswordChallengeConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               SndFactorPasswordChallengeConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", MLSConfig)
                                       (From 'V5
                                        :> (Description ""
                                            :> (ZUser
                                                :> (Summary "Get config for mls"
                                                    :> (CanThrow OperationDenied
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("mls"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        MLSConfig))))))))))))
                                     :<|> Named
                                            '("put", MLSConfig)
                                            (From 'V5
                                             :> (Description ""
                                                 :> (ZUser
                                                     :> (Summary "Put config for mls"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("mls"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (Feature
                                                                                                      MLSConfig)
                                                                                                 :> Put
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         MLSConfig))))))))))))))))
                                    :<|> ((Named
                                             '("get", ExposeInvitationURLsToTeamAdminConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary
                                                        "Get config for exposeInvitationURLsToTeamAdmin"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("exposeInvitationURLsToTeamAdmin"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                           :<|> Named
                                                  '("put", ExposeInvitationURLsToTeamAdminConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for exposeInvitationURLsToTeamAdmin"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("exposeInvitationURLsToTeamAdmin"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        ExposeInvitationURLsToTeamAdminConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", SearchVisibilityInboundConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for searchVisibilityInbound"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("searchVisibilityInbound"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                SearchVisibilityInboundConfig)))))))))))
                                                 :<|> Named
                                                        '("put", SearchVisibilityInboundConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for searchVisibilityInbound"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("searchVisibilityInbound"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              SearchVisibilityInboundConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 SearchVisibilityInboundConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", OutlookCalIntegrationConfig)
                                                         (Description ""
                                                          :> (ZUser
                                                              :> (Summary
                                                                    "Get config for outlookCalIntegration"
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("teams"
                                                                                  :> (Capture
                                                                                        "tid" TeamId
                                                                                      :> ("features"
                                                                                          :> ("outlookCalIntegration"
                                                                                              :> Get
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      OutlookCalIntegrationConfig)))))))))))
                                                       :<|> Named
                                                              '("put", OutlookCalIntegrationConfig)
                                                              (Description ""
                                                               :> (ZUser
                                                                   :> (Summary
                                                                         "Put config for outlookCalIntegration"
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     'TeamNotFound
                                                                                   :> (CanThrow
                                                                                         TeamFeatureError
                                                                                       :> (CanThrowMany
                                                                                             '[]
                                                                                           :> ("teams"
                                                                                               :> (Capture
                                                                                                     "tid"
                                                                                                     TeamId
                                                                                                   :> ("features"
                                                                                                       :> ("outlookCalIntegration"
                                                                                                           :> (ReqBody
                                                                                                                 '[JSON]
                                                                                                                 (Feature
                                                                                                                    OutlookCalIntegrationConfig)
                                                                                                               :> Put
                                                                                                                    '[JSON]
                                                                                                                    (LockableFeature
                                                                                                                       OutlookCalIntegrationConfig)))))))))))))))
                                                      :<|> (Named
                                                              '("get", MlsE2EIdConfig)
                                                              (From 'V5
                                                               :> (Description ""
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Get config for mlsE2EId"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("mlsE2EId"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               MlsE2EIdConfig))))))))))))
                                                            :<|> (Named
                                                                    "put-MlsE2EIdConfig@v5"
                                                                    (From 'V5
                                                                     :> (Until 'V6
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Put config for mlsE2EId"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("mlsE2EId"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (Feature
                                                                                                                              MlsE2EIdConfig)
                                                                                                                         :> Put
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 MlsE2EIdConfig)))))))))))))))
                                                                  :<|> (Named
                                                                          '("put", MlsE2EIdConfig)
                                                                          (From 'V6
                                                                           :> (Description ""
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Put config for mlsE2EId"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("mlsE2EId"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (Feature
                                                                                                                                    MlsE2EIdConfig)
                                                                                                                               :> Put
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       MlsE2EIdConfig)))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get",
                                                                                   MlsMigrationConfig)
                                                                                 (From 'V5
                                                                                  :> (Description ""
                                                                                      :> (ZUser
                                                                                          :> (Summary
                                                                                                "Get config for mlsMigration"
                                                                                              :> (CanThrow
                                                                                                    OperationDenied
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("mlsMigration"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  MlsMigrationConfig))))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        MlsMigrationConfig)
                                                                                      (From 'V5
                                                                                       :> (Description
                                                                                             ""
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Put config for mlsMigration"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("mlsMigration"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (Feature
                                                                                                                                                MlsMigrationConfig)
                                                                                                                                           :> Put
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   MlsMigrationConfig))))))))))))))))
                                                                              :<|> ((Named
                                                                                       '("get",
                                                                                         EnforceFileDownloadLocationConfig)
                                                                                       (From 'V5
                                                                                        :> (Description
                                                                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                            :> (ZUser
                                                                                                :> (Summary
                                                                                                      "Get config for enforceFileDownloadLocation"
                                                                                                    :> (CanThrow
                                                                                                          OperationDenied
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("enforceFileDownloadLocation"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        EnforceFileDownloadLocationConfig))))))))))))
                                                                                     :<|> Named
                                                                                            '("put",
                                                                                              EnforceFileDownloadLocationConfig)
                                                                                            (From
                                                                                               'V5
                                                                                             :> (Description
                                                                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Put config for enforceFileDownloadLocation"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> (CanThrow
                                                                                                                           TeamFeatureError
                                                                                                                         :> (CanThrowMany
                                                                                                                               '[]
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> ("enforceFileDownloadLocation"
                                                                                                                                             :> (ReqBody
                                                                                                                                                   '[JSON]
                                                                                                                                                   (Feature
                                                                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                                                                 :> Put
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         EnforceFileDownloadLocationConfig))))))))))))))))
                                                                                    :<|> (Named
                                                                                            '("get",
                                                                                              LimitedEventFanoutConfig)
                                                                                            (From
                                                                                               'V5
                                                                                             :> (Description
                                                                                                   ""
                                                                                                 :> (ZUser
                                                                                                     :> (Summary
                                                                                                           "Get config for limitedEventFanout"
                                                                                                         :> (CanThrow
                                                                                                               OperationDenied
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("limitedEventFanout"
                                                                                                                                     :> Get
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             LimitedEventFanoutConfig))))))))))))
                                                                                          :<|> (Named
                                                                                                  "get-all-feature-configs-for-user"
                                                                                                  (Summary
                                                                                                     "Gets feature configs for a user"
                                                                                                   :> (Description
                                                                                                         "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                       :> (DescriptionOAuthScope
                                                                                                             'ReadFeatureConfigs
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> Get
                                                                                                                                    '[JSON]
                                                                                                                                    AllTeamFeatures))))))))
                                                                                                :<|> (Named
                                                                                                        "get-all-feature-configs-for-team"
                                                                                                        (Summary
                                                                                                           "Gets feature configs for a team"
                                                                                                         :> (Description
                                                                                                               "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                             :> (CanThrow
                                                                                                                   'NotATeamMember
                                                                                                                 :> (CanThrow
                                                                                                                       OperationDenied
                                                                                                                     :> (CanThrow
                                                                                                                           'TeamNotFound
                                                                                                                         :> (ZLocalUser
                                                                                                                             :> ("teams"
                                                                                                                                 :> (Capture
                                                                                                                                       "tid"
                                                                                                                                       TeamId
                                                                                                                                     :> ("features"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              AllTeamFeatures)))))))))
                                                                                                      :<|> ((Named
                                                                                                               '("get-deprecated",
                                                                                                                 SearchVisibilityAvailableConfig)
                                                                                                               (ZUser
                                                                                                                :> (Summary
                                                                                                                      "[deprecated] Get config for searchVisibility"
                                                                                                                    :> (Until
                                                                                                                          'V2
                                                                                                                        :> (Description
                                                                                                                              "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                            :> (CanThrow
                                                                                                                                  'NotATeamMember
                                                                                                                                :> (CanThrow
                                                                                                                                      OperationDenied
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("search-visibility"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                SearchVisibilityAvailableConfig))))))))))))
                                                                                                             :<|> (Named
                                                                                                                     '("put-deprecated",
                                                                                                                       SearchVisibilityAvailableConfig)
                                                                                                                     (ZUser
                                                                                                                      :> (Summary
                                                                                                                            "[deprecated] Get config for searchVisibility"
                                                                                                                          :> (Until
                                                                                                                                'V2
                                                                                                                              :> (Description
                                                                                                                                    "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                  :> (CanThrow
                                                                                                                                        'NotATeamMember
                                                                                                                                      :> (CanThrow
                                                                                                                                            OperationDenied
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> (CanThrow
                                                                                                                                                    TeamFeatureError
                                                                                                                                                  :> ("teams"
                                                                                                                                                      :> (Capture
                                                                                                                                                            "tid"
                                                                                                                                                            TeamId
                                                                                                                                                          :> ("features"
                                                                                                                                                              :> ("search-visibility"
                                                                                                                                                                  :> (ReqBody
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (Feature
                                                                                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                                                                                      :> Put
                                                                                                                                                                           '[JSON]
                                                                                                                                                                           (LockableFeature
                                                                                                                                                                              SearchVisibilityAvailableConfig))))))))))))))
                                                                                                                   :<|> (Named
                                                                                                                           '("get-deprecated",
                                                                                                                             ValidateSAMLEmailsConfig)
                                                                                                                           (ZUser
                                                                                                                            :> (Summary
                                                                                                                                  "[deprecated] Get config for validateSAMLemails"
                                                                                                                                :> (Until
                                                                                                                                      'V2
                                                                                                                                    :> (Description
                                                                                                                                          "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                        :> (CanThrow
                                                                                                                                              'NotATeamMember
                                                                                                                                            :> (CanThrow
                                                                                                                                                  OperationDenied
                                                                                                                                                :> (CanThrow
                                                                                                                                                      'TeamNotFound
                                                                                                                                                    :> ("teams"
                                                                                                                                                        :> (Capture
                                                                                                                                                              "tid"
                                                                                                                                                              TeamId
                                                                                                                                                            :> ("features"
                                                                                                                                                                :> ("validate-saml-emails"
                                                                                                                                                                    :> Get
                                                                                                                                                                         '[JSON]
                                                                                                                                                                         (LockableFeature
                                                                                                                                                                            ValidateSAMLEmailsConfig))))))))))))
                                                                                                                         :<|> Named
                                                                                                                                '("get-deprecated",
                                                                                                                                  DigitalSignaturesConfig)
                                                                                                                                (ZUser
                                                                                                                                 :> (Summary
                                                                                                                                       "[deprecated] Get config for digitalSignatures"
                                                                                                                                     :> (Until
                                                                                                                                           'V2
                                                                                                                                         :> (Description
                                                                                                                                               "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("teams"
                                                                                                                                                             :> (Capture
                                                                                                                                                                   "tid"
                                                                                                                                                                   TeamId
                                                                                                                                                                 :> ("features"
                                                                                                                                                                     :> ("digital-signatures"
                                                                                                                                                                         :> Get
                                                                                                                                                                              '[JSON]
                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                 DigitalSignaturesConfig)))))))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      LegalholdConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature legalhold"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("legalhold"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             LegalholdConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            SSOConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature sso"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("sso"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   SSOConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  SearchVisibilityAvailableConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("searchVisibility"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         SearchVisibilityAvailableConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        ValidateSAMLEmailsConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("validateSAMLemails"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               ValidateSAMLEmailsConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              DigitalSignaturesConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("digitalSignatures"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     DigitalSignaturesConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    AppLockConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature appLock"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("appLock"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           AppLockConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          FileSharingConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("fileSharing"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 FileSharingConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                ClassifiedDomainsConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("classifiedDomains"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       ClassifiedDomainsConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      ConferenceCallingConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("conferenceCalling"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             ConferenceCallingConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            SelfDeletingMessagesConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("selfDeletingMessages"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  GuestLinksConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         GuestLinksConfig))))))))))
                                                                                                                                                                              :<|> (Named
                                                                                                                                                                                      '("get-config",
                                                                                                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                                                                                                      (Summary
                                                                                                                                                                                         "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                       :> (Until
                                                                                                                                                                                             'V2
                                                                                                                                                                                           :> (Description
                                                                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                               :> (ZUser
                                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                                         'NotATeamMember
                                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                                             OperationDenied
                                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                                 'TeamNotFound
                                                                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                       :> Get
                                                                                                                                                                                                                            '[JSON]
                                                                                                                                                                                                                            (LockableFeature
                                                                                                                                                                                                                               SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                                    :<|> Named
                                                                                                                                                                                           '("get-config",
                                                                                                                                                                                             MLSConfig)
                                                                                                                                                                                           (Summary
                                                                                                                                                                                              "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                            :> (Until
                                                                                                                                                                                                  'V2
                                                                                                                                                                                                :> (Description
                                                                                                                                                                                                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                                    :> (ZUser
                                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                                              'NotATeamMember
                                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                                  OperationDenied
                                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                                                                    :> ("feature-configs"
                                                                                                                                                                                                                        :> ("mls"
                                                                                                                                                                                                                            :> Get
                                                                                                                                                                                                                                 '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     '("get", ConferenceCallingConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for conferenceCalling"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("conferenceCalling"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature ConferenceCallingConfig)))))))))))
   :<|> Named
          '("put", ConferenceCallingConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for conferenceCalling"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("conferenceCalling"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature ConferenceCallingConfig)
                                                           :> Put
                                                                '[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
     '("get", ConferenceCallingConfig)
     (Description (FeatureAPIDesc ConferenceCallingConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol
                   "Get config for " (FeatureSymbol ConferenceCallingConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol ConferenceCallingConfig
                                          :> Get
                                               '[JSON]
                                               (LockableFeature ConferenceCallingConfig)))))))))))
   :<|> Named
          '("put", ConferenceCallingConfig)
          (Description (FeatureAPIDesc ConferenceCallingConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol
                        "Put config for " (FeatureSymbol ConferenceCallingConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors ConferenceCallingConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol ConferenceCallingConfig
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature ConferenceCallingConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", ConferenceCallingConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for conferenceCalling"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("conferenceCalling"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature ConferenceCallingConfig)))))))))))
   :<|> Named
          '("put", ConferenceCallingConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for conferenceCalling"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("conferenceCalling"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature ConferenceCallingConfig)
                                                           :> Put
                                                                '[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
         '("get", SelfDeletingMessagesConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for selfDeletingMessages"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("selfDeletingMessages"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      SelfDeletingMessagesConfig)))))))))))
       :<|> Named
              '("put", SelfDeletingMessagesConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for selfDeletingMessages"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("selfDeletingMessages"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    SelfDeletingMessagesConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       SelfDeletingMessagesConfig)))))))))))))))
      :<|> ((Named
               '("get", GuestLinksConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for conversationGuestLinks"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("conversationGuestLinks"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            GuestLinksConfig)))))))))))
             :<|> Named
                    '("put", GuestLinksConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for conversationGuestLinks"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("conversationGuestLinks"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature GuestLinksConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             GuestLinksConfig)))))))))))))))
            :<|> ((Named
                     '("get", SndFactorPasswordChallengeConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for sndFactorPasswordChallenge"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("sndFactorPasswordChallenge"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  SndFactorPasswordChallengeConfig)))))))))))
                   :<|> Named
                          '("put", SndFactorPasswordChallengeConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for sndFactorPasswordChallenge"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("sndFactorPasswordChallenge"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                SndFactorPasswordChallengeConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   SndFactorPasswordChallengeConfig)))))))))))))))
                  :<|> ((Named
                           '("get", MLSConfig)
                           (From 'V5
                            :> (Description ""
                                :> (ZUser
                                    :> (Summary "Get config for mls"
                                        :> (CanThrow OperationDenied
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("mls"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            MLSConfig))))))))))))
                         :<|> Named
                                '("put", MLSConfig)
                                (From 'V5
                                 :> (Description ""
                                     :> (ZUser
                                         :> (Summary "Put config for mls"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("mls"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (Feature
                                                                                          MLSConfig)
                                                                                     :> Put
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             MLSConfig))))))))))))))))
                        :<|> ((Named
                                 '("get", ExposeInvitationURLsToTeamAdminConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              ExposeInvitationURLsToTeamAdminConfig)))))))))))
                               :<|> Named
                                      '("put", ExposeInvitationURLsToTeamAdminConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary
                                                 "Put config for exposeInvitationURLsToTeamAdmin"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("exposeInvitationURLsToTeamAdmin"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", SearchVisibilityInboundConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for searchVisibilityInbound"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("searchVisibilityInbound"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    SearchVisibilityInboundConfig)))))))))))
                                     :<|> Named
                                            '("put", SearchVisibilityInboundConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary
                                                       "Put config for searchVisibilityInbound"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("searchVisibilityInbound"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  SearchVisibilityInboundConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     SearchVisibilityInboundConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", OutlookCalIntegrationConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary "Get config for outlookCalIntegration"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("outlookCalIntegration"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          OutlookCalIntegrationConfig)))))))))))
                                           :<|> Named
                                                  '("put", OutlookCalIntegrationConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for outlookCalIntegration"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("outlookCalIntegration"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        OutlookCalIntegrationConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           OutlookCalIntegrationConfig)))))))))))))))
                                          :<|> (Named
                                                  '("get", MlsE2EIdConfig)
                                                  (From 'V5
                                                   :> (Description ""
                                                       :> (ZUser
                                                           :> (Summary "Get config for mlsE2EId"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("mlsE2EId"
                                                                                           :> Get
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   MlsE2EIdConfig))))))))))))
                                                :<|> (Named
                                                        "put-MlsE2EIdConfig@v5"
                                                        (From 'V5
                                                         :> (Until 'V6
                                                             :> (ZUser
                                                                 :> (Summary
                                                                       "Put config for mlsE2EId"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("mlsE2EId"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (Feature
                                                                                                                  MlsE2EIdConfig)
                                                                                                             :> Put
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     MlsE2EIdConfig)))))))))))))))
                                                      :<|> (Named
                                                              '("put", MlsE2EIdConfig)
                                                              (From 'V6
                                                               :> (Description ""
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Put config for mlsE2EId"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("mlsE2EId"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (Feature
                                                                                                                        MlsE2EIdConfig)
                                                                                                                   :> Put
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get", MlsMigrationConfig)
                                                                     (From 'V5
                                                                      :> (Description ""
                                                                          :> (ZUser
                                                                              :> (Summary
                                                                                    "Get config for mlsMigration"
                                                                                  :> (CanThrow
                                                                                        OperationDenied
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mlsMigration"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      MlsMigrationConfig))))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            MlsMigrationConfig)
                                                                          (From 'V5
                                                                           :> (Description ""
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Put config for mlsMigration"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("mlsMigration"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (Feature
                                                                                                                                    MlsMigrationConfig)
                                                                                                                               :> Put
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       MlsMigrationConfig))))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             EnforceFileDownloadLocationConfig)
                                                                           (From 'V5
                                                                            :> (Description
                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                :> (ZUser
                                                                                    :> (Summary
                                                                                          "Get config for enforceFileDownloadLocation"
                                                                                        :> (CanThrow
                                                                                              OperationDenied
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            EnforceFileDownloadLocationConfig))))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  EnforceFileDownloadLocationConfig)
                                                                                (From 'V5
                                                                                 :> (Description
                                                                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Put config for enforceFileDownloadLocation"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (Feature
                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                     :> Put
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             EnforceFileDownloadLocationConfig))))))))))))))))
                                                                        :<|> (Named
                                                                                '("get",
                                                                                  LimitedEventFanoutConfig)
                                                                                (From 'V5
                                                                                 :> (Description ""
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Get config for limitedEventFanout"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("limitedEventFanout"
                                                                                                                         :> Get
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 LimitedEventFanoutConfig))))))))))))
                                                                              :<|> (Named
                                                                                      "get-all-feature-configs-for-user"
                                                                                      (Summary
                                                                                         "Gets feature configs for a user"
                                                                                       :> (Description
                                                                                             "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                           :> (DescriptionOAuthScope
                                                                                                 'ReadFeatureConfigs
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        AllTeamFeatures))))))))
                                                                                    :<|> (Named
                                                                                            "get-all-feature-configs-for-team"
                                                                                            (Summary
                                                                                               "Gets feature configs for a team"
                                                                                             :> (Description
                                                                                                   "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (ZLocalUser
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  AllTeamFeatures)))))))))
                                                                                          :<|> ((Named
                                                                                                   '("get-deprecated",
                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                   (ZUser
                                                                                                    :> (Summary
                                                                                                          "[deprecated] Get config for searchVisibility"
                                                                                                        :> (Until
                                                                                                              'V2
                                                                                                            :> (Description
                                                                                                                  "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          OperationDenied
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("search-visibility"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    SearchVisibilityAvailableConfig))))))))))))
                                                                                                 :<|> (Named
                                                                                                         '("put-deprecated",
                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                         (ZUser
                                                                                                          :> (Summary
                                                                                                                "[deprecated] Get config for searchVisibility"
                                                                                                              :> (Until
                                                                                                                    'V2
                                                                                                                  :> (Description
                                                                                                                        "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                OperationDenied
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> ("teams"
                                                                                                                                          :> (Capture
                                                                                                                                                "tid"
                                                                                                                                                TeamId
                                                                                                                                              :> ("features"
                                                                                                                                                  :> ("search-visibility"
                                                                                                                                                      :> (ReqBody
                                                                                                                                                            '[JSON]
                                                                                                                                                            (Feature
                                                                                                                                                               SearchVisibilityAvailableConfig)
                                                                                                                                                          :> Put
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeature
                                                                                                                                                                  SearchVisibilityAvailableConfig))))))))))))))
                                                                                                       :<|> (Named
                                                                                                               '("get-deprecated",
                                                                                                                 ValidateSAMLEmailsConfig)
                                                                                                               (ZUser
                                                                                                                :> (Summary
                                                                                                                      "[deprecated] Get config for validateSAMLemails"
                                                                                                                    :> (Until
                                                                                                                          'V2
                                                                                                                        :> (Description
                                                                                                                              "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                            :> (CanThrow
                                                                                                                                  'NotATeamMember
                                                                                                                                :> (CanThrow
                                                                                                                                      OperationDenied
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("validate-saml-emails"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                ValidateSAMLEmailsConfig))))))))))))
                                                                                                             :<|> Named
                                                                                                                    '("get-deprecated",
                                                                                                                      DigitalSignaturesConfig)
                                                                                                                    (ZUser
                                                                                                                     :> (Summary
                                                                                                                           "[deprecated] Get config for digitalSignatures"
                                                                                                                         :> (Until
                                                                                                                               'V2
                                                                                                                             :> (Description
                                                                                                                                   "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("digital-signatures"
                                                                                                                                                             :> Get
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     DigitalSignaturesConfig)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          LegalholdConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature legalhold"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("legalhold"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 LegalholdConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                SSOConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature sso"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("sso"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       SSOConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      SearchVisibilityAvailableConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("searchVisibility"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             SearchVisibilityAvailableConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            ValidateSAMLEmailsConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("validateSAMLemails"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   ValidateSAMLEmailsConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  DigitalSignaturesConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("digitalSignatures"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         DigitalSignaturesConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        AppLockConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature appLock"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("appLock"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               AppLockConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              FileSharingConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("fileSharing"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     FileSharingConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    ClassifiedDomainsConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("classifiedDomains"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           ClassifiedDomainsConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          ConferenceCallingConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("conferenceCalling"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 ConferenceCallingConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                SelfDeletingMessagesConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("selfDeletingMessages"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       SelfDeletingMessagesConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      GuestLinksConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             GuestLinksConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                        :<|> Named
                                                                                                                                                                               '("get-config",
                                                                                                                                                                                 MLSConfig)
                                                                                                                                                                               (Summary
                                                                                                                                                                                  "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                :> (Until
                                                                                                                                                                                      'V2
                                                                                                                                                                                    :> (Description
                                                                                                                                                                                          "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                        :> (ZUser
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                        :> ("feature-configs"
                                                                                                                                                                                                            :> ("mls"
                                                                                                                                                                                                                :> Get
                                                                                                                                                                                                                     '[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
         '("get", ConferenceCallingConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for conferenceCalling"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("conferenceCalling"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      ConferenceCallingConfig)))))))))))
       :<|> Named
              '("put", ConferenceCallingConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for conferenceCalling"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("conferenceCalling"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature ConferenceCallingConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       ConferenceCallingConfig)))))))))))))))
      :<|> ((Named
               '("get", SelfDeletingMessagesConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for selfDeletingMessages"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("selfDeletingMessages"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            SelfDeletingMessagesConfig)))))))))))
             :<|> Named
                    '("put", SelfDeletingMessagesConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for selfDeletingMessages"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("selfDeletingMessages"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          SelfDeletingMessagesConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             SelfDeletingMessagesConfig)))))))))))))))
            :<|> ((Named
                     '("get", GuestLinksConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for conversationGuestLinks"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("conversationGuestLinks"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  GuestLinksConfig)))))))))))
                   :<|> Named
                          '("put", GuestLinksConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for conversationGuestLinks"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("conversationGuestLinks"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                GuestLinksConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   GuestLinksConfig)))))))))))))))
                  :<|> ((Named
                           '("get", SndFactorPasswordChallengeConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for sndFactorPasswordChallenge"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("sndFactorPasswordChallenge"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        SndFactorPasswordChallengeConfig)))))))))))
                         :<|> Named
                                '("put", SndFactorPasswordChallengeConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for sndFactorPasswordChallenge"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("sndFactorPasswordChallenge"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      SndFactorPasswordChallengeConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         SndFactorPasswordChallengeConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", MLSConfig)
                                 (From 'V5
                                  :> (Description ""
                                      :> (ZUser
                                          :> (Summary "Get config for mls"
                                              :> (CanThrow OperationDenied
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("mls"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  MLSConfig))))))))))))
                               :<|> Named
                                      '("put", MLSConfig)
                                      (From 'V5
                                       :> (Description ""
                                           :> (ZUser
                                               :> (Summary "Put config for mls"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("mls"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (Feature
                                                                                                MLSConfig)
                                                                                           :> Put
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   MLSConfig))))))))))))))))
                              :<|> ((Named
                                       '("get", ExposeInvitationURLsToTeamAdminConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary
                                                  "Get config for exposeInvitationURLsToTeamAdmin"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("exposeInvitationURLsToTeamAdmin"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    ExposeInvitationURLsToTeamAdminConfig)))))))))))
                                     :<|> Named
                                            '("put", ExposeInvitationURLsToTeamAdminConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary
                                                       "Put config for exposeInvitationURLsToTeamAdmin"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("exposeInvitationURLsToTeamAdmin"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  ExposeInvitationURLsToTeamAdminConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", SearchVisibilityInboundConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary
                                                        "Get config for searchVisibilityInbound"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("searchVisibilityInbound"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          SearchVisibilityInboundConfig)))))))))))
                                           :<|> Named
                                                  '("put", SearchVisibilityInboundConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for searchVisibilityInbound"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("searchVisibilityInbound"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        SearchVisibilityInboundConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           SearchVisibilityInboundConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", OutlookCalIntegrationConfig)
                                                   (Description ""
                                                    :> (ZUser
                                                        :> (Summary
                                                              "Get config for outlookCalIntegration"
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("teams"
                                                                            :> (Capture "tid" TeamId
                                                                                :> ("features"
                                                                                    :> ("outlookCalIntegration"
                                                                                        :> Get
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                OutlookCalIntegrationConfig)))))))))))
                                                 :<|> Named
                                                        '("put", OutlookCalIntegrationConfig)
                                                        (Description ""
                                                         :> (ZUser
                                                             :> (Summary
                                                                   "Put config for outlookCalIntegration"
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow 'TeamNotFound
                                                                             :> (CanThrow
                                                                                   TeamFeatureError
                                                                                 :> (CanThrowMany
                                                                                       '[]
                                                                                     :> ("teams"
                                                                                         :> (Capture
                                                                                               "tid"
                                                                                               TeamId
                                                                                             :> ("features"
                                                                                                 :> ("outlookCalIntegration"
                                                                                                     :> (ReqBody
                                                                                                           '[JSON]
                                                                                                           (Feature
                                                                                                              OutlookCalIntegrationConfig)
                                                                                                         :> Put
                                                                                                              '[JSON]
                                                                                                              (LockableFeature
                                                                                                                 OutlookCalIntegrationConfig)))))))))))))))
                                                :<|> (Named
                                                        '("get", MlsE2EIdConfig)
                                                        (From 'V5
                                                         :> (Description ""
                                                             :> (ZUser
                                                                 :> (Summary
                                                                       "Get config for mlsE2EId"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("mlsE2EId"
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         MlsE2EIdConfig))))))))))))
                                                      :<|> (Named
                                                              "put-MlsE2EIdConfig@v5"
                                                              (From 'V5
                                                               :> (Until 'V6
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Put config for mlsE2EId"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("mlsE2EId"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (Feature
                                                                                                                        MlsE2EIdConfig)
                                                                                                                   :> Put
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                            :<|> (Named
                                                                    '("put", MlsE2EIdConfig)
                                                                    (From 'V6
                                                                     :> (Description ""
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Put config for mlsE2EId"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("mlsE2EId"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (Feature
                                                                                                                              MlsE2EIdConfig)
                                                                                                                         :> Put
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 MlsE2EIdConfig)))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             MlsMigrationConfig)
                                                                           (From 'V5
                                                                            :> (Description ""
                                                                                :> (ZUser
                                                                                    :> (Summary
                                                                                          "Get config for mlsMigration"
                                                                                        :> (CanThrow
                                                                                              OperationDenied
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("mlsMigration"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            MlsMigrationConfig))))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  MlsMigrationConfig)
                                                                                (From 'V5
                                                                                 :> (Description ""
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Put config for mlsMigration"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("mlsMigration"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (Feature
                                                                                                                                          MlsMigrationConfig)
                                                                                                                                     :> Put
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             MlsMigrationConfig))))))))))))))))
                                                                        :<|> ((Named
                                                                                 '("get",
                                                                                   EnforceFileDownloadLocationConfig)
                                                                                 (From 'V5
                                                                                  :> (Description
                                                                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                      :> (ZUser
                                                                                          :> (Summary
                                                                                                "Get config for enforceFileDownloadLocation"
                                                                                              :> (CanThrow
                                                                                                    OperationDenied
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("enforceFileDownloadLocation"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  EnforceFileDownloadLocationConfig))))))))))))
                                                                               :<|> Named
                                                                                      '("put",
                                                                                        EnforceFileDownloadLocationConfig)
                                                                                      (From 'V5
                                                                                       :> (Description
                                                                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Put config for enforceFileDownloadLocation"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> (CanThrow
                                                                                                                     TeamFeatureError
                                                                                                                   :> (CanThrowMany
                                                                                                                         '[]
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> ("enforceFileDownloadLocation"
                                                                                                                                       :> (ReqBody
                                                                                                                                             '[JSON]
                                                                                                                                             (Feature
                                                                                                                                                EnforceFileDownloadLocationConfig)
                                                                                                                                           :> Put
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   EnforceFileDownloadLocationConfig))))))))))))))))
                                                                              :<|> (Named
                                                                                      '("get",
                                                                                        LimitedEventFanoutConfig)
                                                                                      (From 'V5
                                                                                       :> (Description
                                                                                             ""
                                                                                           :> (ZUser
                                                                                               :> (Summary
                                                                                                     "Get config for limitedEventFanout"
                                                                                                   :> (CanThrow
                                                                                                         OperationDenied
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("limitedEventFanout"
                                                                                                                               :> Get
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       LimitedEventFanoutConfig))))))))))))
                                                                                    :<|> (Named
                                                                                            "get-all-feature-configs-for-user"
                                                                                            (Summary
                                                                                               "Gets feature configs for a user"
                                                                                             :> (Description
                                                                                                   "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                                 :> (DescriptionOAuthScope
                                                                                                       'ReadFeatureConfigs
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> Get
                                                                                                                              '[JSON]
                                                                                                                              AllTeamFeatures))))))))
                                                                                          :<|> (Named
                                                                                                  "get-all-feature-configs-for-team"
                                                                                                  (Summary
                                                                                                     "Gets feature configs for a team"
                                                                                                   :> (Description
                                                                                                         "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                       :> (CanThrow
                                                                                                             'NotATeamMember
                                                                                                           :> (CanThrow
                                                                                                                 OperationDenied
                                                                                                               :> (CanThrow
                                                                                                                     'TeamNotFound
                                                                                                                   :> (ZLocalUser
                                                                                                                       :> ("teams"
                                                                                                                           :> (Capture
                                                                                                                                 "tid"
                                                                                                                                 TeamId
                                                                                                                               :> ("features"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        AllTeamFeatures)))))))))
                                                                                                :<|> ((Named
                                                                                                         '("get-deprecated",
                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                         (ZUser
                                                                                                          :> (Summary
                                                                                                                "[deprecated] Get config for searchVisibility"
                                                                                                              :> (Until
                                                                                                                    'V2
                                                                                                                  :> (Description
                                                                                                                        "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                OperationDenied
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("search-visibility"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          SearchVisibilityAvailableConfig))))))))))))
                                                                                                       :<|> (Named
                                                                                                               '("put-deprecated",
                                                                                                                 SearchVisibilityAvailableConfig)
                                                                                                               (ZUser
                                                                                                                :> (Summary
                                                                                                                      "[deprecated] Get config for searchVisibility"
                                                                                                                    :> (Until
                                                                                                                          'V2
                                                                                                                        :> (Description
                                                                                                                              "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                            :> (CanThrow
                                                                                                                                  'NotATeamMember
                                                                                                                                :> (CanThrow
                                                                                                                                      OperationDenied
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> (CanThrow
                                                                                                                                              TeamFeatureError
                                                                                                                                            :> ("teams"
                                                                                                                                                :> (Capture
                                                                                                                                                      "tid"
                                                                                                                                                      TeamId
                                                                                                                                                    :> ("features"
                                                                                                                                                        :> ("search-visibility"
                                                                                                                                                            :> (ReqBody
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (Feature
                                                                                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                                                                                :> Put
                                                                                                                                                                     '[JSON]
                                                                                                                                                                     (LockableFeature
                                                                                                                                                                        SearchVisibilityAvailableConfig))))))))))))))
                                                                                                             :<|> (Named
                                                                                                                     '("get-deprecated",
                                                                                                                       ValidateSAMLEmailsConfig)
                                                                                                                     (ZUser
                                                                                                                      :> (Summary
                                                                                                                            "[deprecated] Get config for validateSAMLemails"
                                                                                                                          :> (Until
                                                                                                                                'V2
                                                                                                                              :> (Description
                                                                                                                                    "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                                  :> (CanThrow
                                                                                                                                        'NotATeamMember
                                                                                                                                      :> (CanThrow
                                                                                                                                            OperationDenied
                                                                                                                                          :> (CanThrow
                                                                                                                                                'TeamNotFound
                                                                                                                                              :> ("teams"
                                                                                                                                                  :> (Capture
                                                                                                                                                        "tid"
                                                                                                                                                        TeamId
                                                                                                                                                      :> ("features"
                                                                                                                                                          :> ("validate-saml-emails"
                                                                                                                                                              :> Get
                                                                                                                                                                   '[JSON]
                                                                                                                                                                   (LockableFeature
                                                                                                                                                                      ValidateSAMLEmailsConfig))))))))))))
                                                                                                                   :<|> Named
                                                                                                                          '("get-deprecated",
                                                                                                                            DigitalSignaturesConfig)
                                                                                                                          (ZUser
                                                                                                                           :> (Summary
                                                                                                                                 "[deprecated] Get config for digitalSignatures"
                                                                                                                               :> (Until
                                                                                                                                     'V2
                                                                                                                                   :> (Description
                                                                                                                                         "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("teams"
                                                                                                                                                       :> (Capture
                                                                                                                                                             "tid"
                                                                                                                                                             TeamId
                                                                                                                                                           :> ("features"
                                                                                                                                                               :> ("digital-signatures"
                                                                                                                                                                   :> Get
                                                                                                                                                                        '[JSON]
                                                                                                                                                                        (LockableFeature
                                                                                                                                                                           DigitalSignaturesConfig)))))))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                LegalholdConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature legalhold"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("legalhold"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       LegalholdConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      SSOConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature sso"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("sso"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             SSOConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            SearchVisibilityAvailableConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("searchVisibility"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   SearchVisibilityAvailableConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  ValidateSAMLEmailsConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("validateSAMLemails"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         ValidateSAMLEmailsConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        DigitalSignaturesConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("digitalSignatures"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               DigitalSignaturesConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              AppLockConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature appLock"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("appLock"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     AppLockConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    FileSharingConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("fileSharing"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           FileSharingConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          ClassifiedDomainsConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("classifiedDomains"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 ClassifiedDomainsConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                ConferenceCallingConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("conferenceCalling"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       ConferenceCallingConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      SelfDeletingMessagesConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("selfDeletingMessages"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             SelfDeletingMessagesConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            GuestLinksConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   GuestLinksConfig))))))))))
                                                                                                                                                                        :<|> (Named
                                                                                                                                                                                '("get-config",
                                                                                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                                                                                (Summary
                                                                                                                                                                                   "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                                 :> (Until
                                                                                                                                                                                       'V2
                                                                                                                                                                                     :> (Description
                                                                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                         :> (ZUser
                                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                                   'NotATeamMember
                                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                                       OperationDenied
                                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                                           'TeamNotFound
                                                                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                                 :> Get
                                                                                                                                                                                                                      '[JSON]
                                                                                                                                                                                                                      (LockableFeature
                                                                                                                                                                                                                         SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                              :<|> Named
                                                                                                                                                                                     '("get-config",
                                                                                                                                                                                       MLSConfig)
                                                                                                                                                                                     (Summary
                                                                                                                                                                                        "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                      :> (Until
                                                                                                                                                                                            'V2
                                                                                                                                                                                          :> (Description
                                                                                                                                                                                                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                              :> (ZUser
                                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                                        'NotATeamMember
                                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                                            OperationDenied
                                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                                'TeamNotFound
                                                                                                                                                                                                              :> ("feature-configs"
                                                                                                                                                                                                                  :> ("mls"
                                                                                                                                                                                                                      :> Get
                                                                                                                                                                                                                           '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     '("get", SelfDeletingMessagesConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for selfDeletingMessages"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("selfDeletingMessages"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SelfDeletingMessagesConfig)))))))))))
   :<|> Named
          '("put", SelfDeletingMessagesConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for selfDeletingMessages"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("selfDeletingMessages"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature SelfDeletingMessagesConfig)
                                                           :> Put
                                                                '[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
     '("get", SelfDeletingMessagesConfig)
     (Description (FeatureAPIDesc SelfDeletingMessagesConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol
                   "Get config for " (FeatureSymbol SelfDeletingMessagesConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol SelfDeletingMessagesConfig
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SelfDeletingMessagesConfig)))))))))))
   :<|> Named
          '("put", SelfDeletingMessagesConfig)
          (Description (FeatureAPIDesc SelfDeletingMessagesConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol
                        "Put config for " (FeatureSymbol SelfDeletingMessagesConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors SelfDeletingMessagesConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol SelfDeletingMessagesConfig
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature SelfDeletingMessagesConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", SelfDeletingMessagesConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for selfDeletingMessages"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("selfDeletingMessages"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SelfDeletingMessagesConfig)))))))))))
   :<|> Named
          '("put", SelfDeletingMessagesConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for selfDeletingMessages"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("selfDeletingMessages"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature SelfDeletingMessagesConfig)
                                                           :> Put
                                                                '[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
         '("get", GuestLinksConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for conversationGuestLinks"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("conversationGuestLinks"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature GuestLinksConfig)))))))))))
       :<|> Named
              '("put", GuestLinksConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for conversationGuestLinks"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("conversationGuestLinks"
                                                           :> (ReqBody
                                                                 '[JSON] (Feature GuestLinksConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       GuestLinksConfig)))))))))))))))
      :<|> ((Named
               '("get", SndFactorPasswordChallengeConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for sndFactorPasswordChallenge"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("sndFactorPasswordChallenge"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            SndFactorPasswordChallengeConfig)))))))))))
             :<|> Named
                    '("put", SndFactorPasswordChallengeConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for sndFactorPasswordChallenge"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("sndFactorPasswordChallenge"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          SndFactorPasswordChallengeConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             SndFactorPasswordChallengeConfig)))))))))))))))
            :<|> ((Named
                     '("get", MLSConfig)
                     (From 'V5
                      :> (Description ""
                          :> (ZUser
                              :> (Summary "Get config for mls"
                                  :> (CanThrow OperationDenied
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mls"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      MLSConfig))))))))))))
                   :<|> Named
                          '("put", MLSConfig)
                          (From 'V5
                           :> (Description ""
                               :> (ZUser
                                   :> (Summary "Put config for mls"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("mls"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (Feature MLSConfig)
                                                                               :> Put
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       MLSConfig))))))))))))))))
                  :<|> ((Named
                           '("get", ExposeInvitationURLsToTeamAdminConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        ExposeInvitationURLsToTeamAdminConfig)))))))))))
                         :<|> Named
                                '("put", ExposeInvitationURLsToTeamAdminConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("exposeInvitationURLsToTeamAdmin"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", SearchVisibilityInboundConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for searchVisibilityInbound"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("searchVisibilityInbound"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              SearchVisibilityInboundConfig)))))))))))
                               :<|> Named
                                      '("put", SearchVisibilityInboundConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for searchVisibilityInbound"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("searchVisibilityInbound"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            SearchVisibilityInboundConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               SearchVisibilityInboundConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", OutlookCalIntegrationConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for outlookCalIntegration"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("outlookCalIntegration"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    OutlookCalIntegrationConfig)))))))))))
                                     :<|> Named
                                            '("put", OutlookCalIntegrationConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Put config for outlookCalIntegration"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("outlookCalIntegration"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  OutlookCalIntegrationConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     OutlookCalIntegrationConfig)))))))))))))))
                                    :<|> (Named
                                            '("get", MlsE2EIdConfig)
                                            (From 'V5
                                             :> (Description ""
                                                 :> (ZUser
                                                     :> (Summary "Get config for mlsE2EId"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("mlsE2EId"
                                                                                     :> Get
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             MlsE2EIdConfig))))))))))))
                                          :<|> (Named
                                                  "put-MlsE2EIdConfig@v5"
                                                  (From 'V5
                                                   :> (Until 'V6
                                                       :> (ZUser
                                                           :> (Summary "Put config for mlsE2EId"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("mlsE2EId"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (Feature
                                                                                                            MlsE2EIdConfig)
                                                                                                       :> Put
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               MlsE2EIdConfig)))))))))))))))
                                                :<|> (Named
                                                        '("put", MlsE2EIdConfig)
                                                        (From 'V6
                                                         :> (Description ""
                                                             :> (ZUser
                                                                 :> (Summary
                                                                       "Put config for mlsE2EId"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("mlsE2EId"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (Feature
                                                                                                                  MlsE2EIdConfig)
                                                                                                             :> Put
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     MlsE2EIdConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get", MlsMigrationConfig)
                                                               (From 'V5
                                                                :> (Description ""
                                                                    :> (ZUser
                                                                        :> (Summary
                                                                              "Get config for mlsMigration"
                                                                            :> (CanThrow
                                                                                  OperationDenied
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mlsMigration"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                MlsMigrationConfig))))))))))))
                                                             :<|> Named
                                                                    '("put", MlsMigrationConfig)
                                                                    (From 'V5
                                                                     :> (Description ""
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Put config for mlsMigration"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("mlsMigration"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (Feature
                                                                                                                              MlsMigrationConfig)
                                                                                                                         :> Put
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 MlsMigrationConfig))))))))))))))))
                                                            :<|> ((Named
                                                                     '("get",
                                                                       EnforceFileDownloadLocationConfig)
                                                                     (From 'V5
                                                                      :> (Description
                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                          :> (ZUser
                                                                              :> (Summary
                                                                                    "Get config for enforceFileDownloadLocation"
                                                                                  :> (CanThrow
                                                                                        OperationDenied
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      EnforceFileDownloadLocationConfig))))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            EnforceFileDownloadLocationConfig)
                                                                          (From 'V5
                                                                           :> (Description
                                                                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Put config for enforceFileDownloadLocation"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("enforceFileDownloadLocation"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (Feature
                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                               :> Put
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       EnforceFileDownloadLocationConfig))))))))))))))))
                                                                  :<|> (Named
                                                                          '("get",
                                                                            LimitedEventFanoutConfig)
                                                                          (From 'V5
                                                                           :> (Description ""
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Get config for limitedEventFanout"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("limitedEventFanout"
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           LimitedEventFanoutConfig))))))))))))
                                                                        :<|> (Named
                                                                                "get-all-feature-configs-for-user"
                                                                                (Summary
                                                                                   "Gets feature configs for a user"
                                                                                 :> (Description
                                                                                       "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                     :> (DescriptionOAuthScope
                                                                                           'ReadFeatureConfigs
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  AllTeamFeatures))))))))
                                                                              :<|> (Named
                                                                                      "get-all-feature-configs-for-team"
                                                                                      (Summary
                                                                                         "Gets feature configs for a team"
                                                                                       :> (Description
                                                                                             "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (ZLocalUser
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            AllTeamFeatures)))))))))
                                                                                    :<|> ((Named
                                                                                             '("get-deprecated",
                                                                                               SearchVisibilityAvailableConfig)
                                                                                             (ZUser
                                                                                              :> (Summary
                                                                                                    "[deprecated] Get config for searchVisibility"
                                                                                                  :> (Until
                                                                                                        'V2
                                                                                                      :> (Description
                                                                                                            "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    OperationDenied
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("search-visibility"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SearchVisibilityAvailableConfig))))))))))))
                                                                                           :<|> (Named
                                                                                                   '("put-deprecated",
                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                   (ZUser
                                                                                                    :> (Summary
                                                                                                          "[deprecated] Get config for searchVisibility"
                                                                                                        :> (Until
                                                                                                              'V2
                                                                                                            :> (Description
                                                                                                                  "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          OperationDenied
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> ("teams"
                                                                                                                                    :> (Capture
                                                                                                                                          "tid"
                                                                                                                                          TeamId
                                                                                                                                        :> ("features"
                                                                                                                                            :> ("search-visibility"
                                                                                                                                                :> (ReqBody
                                                                                                                                                      '[JSON]
                                                                                                                                                      (Feature
                                                                                                                                                         SearchVisibilityAvailableConfig)
                                                                                                                                                    :> Put
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeature
                                                                                                                                                            SearchVisibilityAvailableConfig))))))))))))))
                                                                                                 :<|> (Named
                                                                                                         '("get-deprecated",
                                                                                                           ValidateSAMLEmailsConfig)
                                                                                                         (ZUser
                                                                                                          :> (Summary
                                                                                                                "[deprecated] Get config for validateSAMLemails"
                                                                                                              :> (Until
                                                                                                                    'V2
                                                                                                                  :> (Description
                                                                                                                        "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                OperationDenied
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("validate-saml-emails"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ValidateSAMLEmailsConfig))))))))))))
                                                                                                       :<|> Named
                                                                                                              '("get-deprecated",
                                                                                                                DigitalSignaturesConfig)
                                                                                                              (ZUser
                                                                                                               :> (Summary
                                                                                                                     "[deprecated] Get config for digitalSignatures"
                                                                                                                   :> (Until
                                                                                                                         'V2
                                                                                                                       :> (Description
                                                                                                                             "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("digital-signatures"
                                                                                                                                                       :> Get
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               DigitalSignaturesConfig)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    LegalholdConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature legalhold"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("legalhold"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           LegalholdConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          SSOConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature sso"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("sso"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 SSOConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                SearchVisibilityAvailableConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature searchVisibility"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("searchVisibility"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       SearchVisibilityAvailableConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      ValidateSAMLEmailsConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("validateSAMLemails"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             ValidateSAMLEmailsConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            DigitalSignaturesConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("digitalSignatures"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   DigitalSignaturesConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  AppLockConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature appLock"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("appLock"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         AppLockConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        FileSharingConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("fileSharing"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               FileSharingConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              ClassifiedDomainsConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("classifiedDomains"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     ClassifiedDomainsConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    ConferenceCallingConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("conferenceCalling"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           ConferenceCallingConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          SelfDeletingMessagesConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("selfDeletingMessages"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 SelfDeletingMessagesConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                GuestLinksConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       GuestLinksConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                  :<|> Named
                                                                                                                                                                         '("get-config",
                                                                                                                                                                           MLSConfig)
                                                                                                                                                                         (Summary
                                                                                                                                                                            "[deprecated] Get feature config for feature mls"
                                                                                                                                                                          :> (Until
                                                                                                                                                                                'V2
                                                                                                                                                                              :> (Description
                                                                                                                                                                                    "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                  :> (ZUser
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                  :> ("feature-configs"
                                                                                                                                                                                                      :> ("mls"
                                                                                                                                                                                                          :> Get
                                                                                                                                                                                                               '[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
         '("get", SelfDeletingMessagesConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for selfDeletingMessages"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("selfDeletingMessages"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      SelfDeletingMessagesConfig)))))))))))
       :<|> Named
              '("put", SelfDeletingMessagesConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for selfDeletingMessages"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("selfDeletingMessages"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    SelfDeletingMessagesConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       SelfDeletingMessagesConfig)))))))))))))))
      :<|> ((Named
               '("get", GuestLinksConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for conversationGuestLinks"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("conversationGuestLinks"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            GuestLinksConfig)))))))))))
             :<|> Named
                    '("put", GuestLinksConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for conversationGuestLinks"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("conversationGuestLinks"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature GuestLinksConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             GuestLinksConfig)))))))))))))))
            :<|> ((Named
                     '("get", SndFactorPasswordChallengeConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for sndFactorPasswordChallenge"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("sndFactorPasswordChallenge"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  SndFactorPasswordChallengeConfig)))))))))))
                   :<|> Named
                          '("put", SndFactorPasswordChallengeConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for sndFactorPasswordChallenge"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("sndFactorPasswordChallenge"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                SndFactorPasswordChallengeConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   SndFactorPasswordChallengeConfig)))))))))))))))
                  :<|> ((Named
                           '("get", MLSConfig)
                           (From 'V5
                            :> (Description ""
                                :> (ZUser
                                    :> (Summary "Get config for mls"
                                        :> (CanThrow OperationDenied
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("mls"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            MLSConfig))))))))))))
                         :<|> Named
                                '("put", MLSConfig)
                                (From 'V5
                                 :> (Description ""
                                     :> (ZUser
                                         :> (Summary "Put config for mls"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("mls"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (Feature
                                                                                          MLSConfig)
                                                                                     :> Put
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             MLSConfig))))))))))))))))
                        :<|> ((Named
                                 '("get", ExposeInvitationURLsToTeamAdminConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("exposeInvitationURLsToTeamAdmin"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              ExposeInvitationURLsToTeamAdminConfig)))))))))))
                               :<|> Named
                                      '("put", ExposeInvitationURLsToTeamAdminConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary
                                                 "Put config for exposeInvitationURLsToTeamAdmin"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("exposeInvitationURLsToTeamAdmin"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            ExposeInvitationURLsToTeamAdminConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", SearchVisibilityInboundConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for searchVisibilityInbound"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("searchVisibilityInbound"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    SearchVisibilityInboundConfig)))))))))))
                                     :<|> Named
                                            '("put", SearchVisibilityInboundConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary
                                                       "Put config for searchVisibilityInbound"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("searchVisibilityInbound"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  SearchVisibilityInboundConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     SearchVisibilityInboundConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", OutlookCalIntegrationConfig)
                                             (Description ""
                                              :> (ZUser
                                                  :> (Summary "Get config for outlookCalIntegration"
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("teams"
                                                                      :> (Capture "tid" TeamId
                                                                          :> ("features"
                                                                              :> ("outlookCalIntegration"
                                                                                  :> Get
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          OutlookCalIntegrationConfig)))))))))))
                                           :<|> Named
                                                  '("put", OutlookCalIntegrationConfig)
                                                  (Description ""
                                                   :> (ZUser
                                                       :> (Summary
                                                             "Put config for outlookCalIntegration"
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow 'TeamNotFound
                                                                       :> (CanThrow TeamFeatureError
                                                                           :> (CanThrowMany '[]
                                                                               :> ("teams"
                                                                                   :> (Capture
                                                                                         "tid"
                                                                                         TeamId
                                                                                       :> ("features"
                                                                                           :> ("outlookCalIntegration"
                                                                                               :> (ReqBody
                                                                                                     '[JSON]
                                                                                                     (Feature
                                                                                                        OutlookCalIntegrationConfig)
                                                                                                   :> Put
                                                                                                        '[JSON]
                                                                                                        (LockableFeature
                                                                                                           OutlookCalIntegrationConfig)))))))))))))))
                                          :<|> (Named
                                                  '("get", MlsE2EIdConfig)
                                                  (From 'V5
                                                   :> (Description ""
                                                       :> (ZUser
                                                           :> (Summary "Get config for mlsE2EId"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("mlsE2EId"
                                                                                           :> Get
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   MlsE2EIdConfig))))))))))))
                                                :<|> (Named
                                                        "put-MlsE2EIdConfig@v5"
                                                        (From 'V5
                                                         :> (Until 'V6
                                                             :> (ZUser
                                                                 :> (Summary
                                                                       "Put config for mlsE2EId"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("mlsE2EId"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (Feature
                                                                                                                  MlsE2EIdConfig)
                                                                                                             :> Put
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     MlsE2EIdConfig)))))))))))))))
                                                      :<|> (Named
                                                              '("put", MlsE2EIdConfig)
                                                              (From 'V6
                                                               :> (Description ""
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Put config for mlsE2EId"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("mlsE2EId"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (Feature
                                                                                                                        MlsE2EIdConfig)
                                                                                                                   :> Put
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           MlsE2EIdConfig)))))))))))))))
                                                            :<|> ((Named
                                                                     '("get", MlsMigrationConfig)
                                                                     (From 'V5
                                                                      :> (Description ""
                                                                          :> (ZUser
                                                                              :> (Summary
                                                                                    "Get config for mlsMigration"
                                                                                  :> (CanThrow
                                                                                        OperationDenied
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("mlsMigration"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      MlsMigrationConfig))))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            MlsMigrationConfig)
                                                                          (From 'V5
                                                                           :> (Description ""
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Put config for mlsMigration"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("mlsMigration"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (Feature
                                                                                                                                    MlsMigrationConfig)
                                                                                                                               :> Put
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       MlsMigrationConfig))))))))))))))))
                                                                  :<|> ((Named
                                                                           '("get",
                                                                             EnforceFileDownloadLocationConfig)
                                                                           (From 'V5
                                                                            :> (Description
                                                                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                :> (ZUser
                                                                                    :> (Summary
                                                                                          "Get config for enforceFileDownloadLocation"
                                                                                        :> (CanThrow
                                                                                              OperationDenied
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("enforceFileDownloadLocation"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            EnforceFileDownloadLocationConfig))))))))))))
                                                                         :<|> Named
                                                                                '("put",
                                                                                  EnforceFileDownloadLocationConfig)
                                                                                (From 'V5
                                                                                 :> (Description
                                                                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Put config for enforceFileDownloadLocation"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> (CanThrow
                                                                                                               TeamFeatureError
                                                                                                             :> (CanThrowMany
                                                                                                                   '[]
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> ("enforceFileDownloadLocation"
                                                                                                                                 :> (ReqBody
                                                                                                                                       '[JSON]
                                                                                                                                       (Feature
                                                                                                                                          EnforceFileDownloadLocationConfig)
                                                                                                                                     :> Put
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             EnforceFileDownloadLocationConfig))))))))))))))))
                                                                        :<|> (Named
                                                                                '("get",
                                                                                  LimitedEventFanoutConfig)
                                                                                (From 'V5
                                                                                 :> (Description ""
                                                                                     :> (ZUser
                                                                                         :> (Summary
                                                                                               "Get config for limitedEventFanout"
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("limitedEventFanout"
                                                                                                                         :> Get
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 LimitedEventFanoutConfig))))))))))))
                                                                              :<|> (Named
                                                                                      "get-all-feature-configs-for-user"
                                                                                      (Summary
                                                                                         "Gets feature configs for a user"
                                                                                       :> (Description
                                                                                             "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                           :> (DescriptionOAuthScope
                                                                                                 'ReadFeatureConfigs
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        AllTeamFeatures))))))))
                                                                                    :<|> (Named
                                                                                            "get-all-feature-configs-for-team"
                                                                                            (Summary
                                                                                               "Gets feature configs for a team"
                                                                                             :> (Description
                                                                                                   "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                                 :> (CanThrow
                                                                                                       'NotATeamMember
                                                                                                     :> (CanThrow
                                                                                                           OperationDenied
                                                                                                         :> (CanThrow
                                                                                                               'TeamNotFound
                                                                                                             :> (ZLocalUser
                                                                                                                 :> ("teams"
                                                                                                                     :> (Capture
                                                                                                                           "tid"
                                                                                                                           TeamId
                                                                                                                         :> ("features"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  AllTeamFeatures)))))))))
                                                                                          :<|> ((Named
                                                                                                   '("get-deprecated",
                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                   (ZUser
                                                                                                    :> (Summary
                                                                                                          "[deprecated] Get config for searchVisibility"
                                                                                                        :> (Until
                                                                                                              'V2
                                                                                                            :> (Description
                                                                                                                  "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          OperationDenied
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("search-visibility"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    SearchVisibilityAvailableConfig))))))))))))
                                                                                                 :<|> (Named
                                                                                                         '("put-deprecated",
                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                         (ZUser
                                                                                                          :> (Summary
                                                                                                                "[deprecated] Get config for searchVisibility"
                                                                                                              :> (Until
                                                                                                                    'V2
                                                                                                                  :> (Description
                                                                                                                        "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                OperationDenied
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> (CanThrow
                                                                                                                                        TeamFeatureError
                                                                                                                                      :> ("teams"
                                                                                                                                          :> (Capture
                                                                                                                                                "tid"
                                                                                                                                                TeamId
                                                                                                                                              :> ("features"
                                                                                                                                                  :> ("search-visibility"
                                                                                                                                                      :> (ReqBody
                                                                                                                                                            '[JSON]
                                                                                                                                                            (Feature
                                                                                                                                                               SearchVisibilityAvailableConfig)
                                                                                                                                                          :> Put
                                                                                                                                                               '[JSON]
                                                                                                                                                               (LockableFeature
                                                                                                                                                                  SearchVisibilityAvailableConfig))))))))))))))
                                                                                                       :<|> (Named
                                                                                                               '("get-deprecated",
                                                                                                                 ValidateSAMLEmailsConfig)
                                                                                                               (ZUser
                                                                                                                :> (Summary
                                                                                                                      "[deprecated] Get config for validateSAMLemails"
                                                                                                                    :> (Until
                                                                                                                          'V2
                                                                                                                        :> (Description
                                                                                                                              "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                            :> (CanThrow
                                                                                                                                  'NotATeamMember
                                                                                                                                :> (CanThrow
                                                                                                                                      OperationDenied
                                                                                                                                    :> (CanThrow
                                                                                                                                          'TeamNotFound
                                                                                                                                        :> ("teams"
                                                                                                                                            :> (Capture
                                                                                                                                                  "tid"
                                                                                                                                                  TeamId
                                                                                                                                                :> ("features"
                                                                                                                                                    :> ("validate-saml-emails"
                                                                                                                                                        :> Get
                                                                                                                                                             '[JSON]
                                                                                                                                                             (LockableFeature
                                                                                                                                                                ValidateSAMLEmailsConfig))))))))))))
                                                                                                             :<|> Named
                                                                                                                    '("get-deprecated",
                                                                                                                      DigitalSignaturesConfig)
                                                                                                                    (ZUser
                                                                                                                     :> (Summary
                                                                                                                           "[deprecated] Get config for digitalSignatures"
                                                                                                                         :> (Until
                                                                                                                               'V2
                                                                                                                             :> (Description
                                                                                                                                   "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("teams"
                                                                                                                                                 :> (Capture
                                                                                                                                                       "tid"
                                                                                                                                                       TeamId
                                                                                                                                                     :> ("features"
                                                                                                                                                         :> ("digital-signatures"
                                                                                                                                                             :> Get
                                                                                                                                                                  '[JSON]
                                                                                                                                                                  (LockableFeature
                                                                                                                                                                     DigitalSignaturesConfig)))))))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          LegalholdConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature legalhold"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("legalhold"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 LegalholdConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                SSOConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature sso"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("sso"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       SSOConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      SearchVisibilityAvailableConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature searchVisibility"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("searchVisibility"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             SearchVisibilityAvailableConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            ValidateSAMLEmailsConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("validateSAMLemails"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   ValidateSAMLEmailsConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  DigitalSignaturesConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("digitalSignatures"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         DigitalSignaturesConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        AppLockConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature appLock"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("appLock"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               AppLockConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              FileSharingConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("fileSharing"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     FileSharingConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    ClassifiedDomainsConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("classifiedDomains"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           ClassifiedDomainsConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          ConferenceCallingConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("conferenceCalling"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 ConferenceCallingConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                SelfDeletingMessagesConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("selfDeletingMessages"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       SelfDeletingMessagesConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      GuestLinksConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             GuestLinksConfig))))))))))
                                                                                                                                                                  :<|> (Named
                                                                                                                                                                          '("get-config",
                                                                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                                                                          (Summary
                                                                                                                                                                             "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                           :> (Until
                                                                                                                                                                                 'V2
                                                                                                                                                                               :> (Description
                                                                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                   :> (ZUser
                                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                                             'NotATeamMember
                                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                                 OperationDenied
                                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                                     'TeamNotFound
                                                                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                           :> Get
                                                                                                                                                                                                                '[JSON]
                                                                                                                                                                                                                (LockableFeature
                                                                                                                                                                                                                   SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                        :<|> Named
                                                                                                                                                                               '("get-config",
                                                                                                                                                                                 MLSConfig)
                                                                                                                                                                               (Summary
                                                                                                                                                                                  "[deprecated] Get feature config for feature mls"
                                                                                                                                                                                :> (Until
                                                                                                                                                                                      'V2
                                                                                                                                                                                    :> (Description
                                                                                                                                                                                          "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                        :> (ZUser
                                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                                  'NotATeamMember
                                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                                      OperationDenied
                                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                                          'TeamNotFound
                                                                                                                                                                                                        :> ("feature-configs"
                                                                                                                                                                                                            :> ("mls"
                                                                                                                                                                                                                :> Get
                                                                                                                                                                                                                     '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     '("get", GuestLinksConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for conversationGuestLinks"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("conversationGuestLinks"
                                          :> Get
                                               '[JSON] (LockableFeature GuestLinksConfig)))))))))))
   :<|> Named
          '("put", GuestLinksConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for conversationGuestLinks"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("conversationGuestLinks"
                                                       :> (ReqBody
                                                             '[JSON] (Feature GuestLinksConfig)
                                                           :> Put
                                                                '[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
     '("get", GuestLinksConfig)
     (Description (FeatureAPIDesc GuestLinksConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol "Get config for " (FeatureSymbol GuestLinksConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol GuestLinksConfig
                                          :> Get
                                               '[JSON] (LockableFeature GuestLinksConfig)))))))))))
   :<|> Named
          '("put", GuestLinksConfig)
          (Description (FeatureAPIDesc GuestLinksConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol "Put config for " (FeatureSymbol GuestLinksConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors GuestLinksConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol GuestLinksConfig
                                                       :> (ReqBody
                                                             '[JSON] (Feature GuestLinksConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", GuestLinksConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for conversationGuestLinks"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("conversationGuestLinks"
                                          :> Get
                                               '[JSON] (LockableFeature GuestLinksConfig)))))))))))
   :<|> Named
          '("put", GuestLinksConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for conversationGuestLinks"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("conversationGuestLinks"
                                                       :> (ReqBody
                                                             '[JSON] (Feature GuestLinksConfig)
                                                           :> Put
                                                                '[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
         '("get", SndFactorPasswordChallengeConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for sndFactorPasswordChallenge"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("sndFactorPasswordChallenge"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      SndFactorPasswordChallengeConfig)))))))))))
       :<|> Named
              '("put", SndFactorPasswordChallengeConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for sndFactorPasswordChallenge"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("sndFactorPasswordChallenge"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    SndFactorPasswordChallengeConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       SndFactorPasswordChallengeConfig)))))))))))))))
      :<|> ((Named
               '("get", MLSConfig)
               (From 'V5
                :> (Description ""
                    :> (ZUser
                        :> (Summary "Get config for mls"
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("mls"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature MLSConfig))))))))))))
             :<|> Named
                    '("put", MLSConfig)
                    (From 'V5
                     :> (Description ""
                         :> (ZUser
                             :> (Summary "Put config for mls"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany '[]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("mls"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (Feature MLSConfig)
                                                                         :> Put
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 MLSConfig))))))))))))))))
            :<|> ((Named
                     '("get", ExposeInvitationURLsToTeamAdminConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  ExposeInvitationURLsToTeamAdminConfig)))))))))))
                   :<|> Named
                          '("put", ExposeInvitationURLsToTeamAdminConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("exposeInvitationURLsToTeamAdmin"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                  :<|> ((Named
                           '("get", SearchVisibilityInboundConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for searchVisibilityInbound"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("searchVisibilityInbound"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        SearchVisibilityInboundConfig)))))))))))
                         :<|> Named
                                '("put", SearchVisibilityInboundConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for searchVisibilityInbound"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("searchVisibilityInbound"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      SearchVisibilityInboundConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         SearchVisibilityInboundConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", OutlookCalIntegrationConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for outlookCalIntegration"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("outlookCalIntegration"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              OutlookCalIntegrationConfig)))))))))))
                               :<|> Named
                                      '("put", OutlookCalIntegrationConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for outlookCalIntegration"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("outlookCalIntegration"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            OutlookCalIntegrationConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               OutlookCalIntegrationConfig)))))))))))))))
                              :<|> (Named
                                      '("get", MlsE2EIdConfig)
                                      (From 'V5
                                       :> (Description ""
                                           :> (ZUser
                                               :> (Summary "Get config for mlsE2EId"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("mlsE2EId"
                                                                               :> Get
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       MlsE2EIdConfig))))))))))))
                                    :<|> (Named
                                            "put-MlsE2EIdConfig@v5"
                                            (From 'V5
                                             :> (Until 'V6
                                                 :> (ZUser
                                                     :> (Summary "Put config for mlsE2EId"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("mlsE2EId"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (Feature
                                                                                                      MlsE2EIdConfig)
                                                                                                 :> Put
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         MlsE2EIdConfig)))))))))))))))
                                          :<|> (Named
                                                  '("put", MlsE2EIdConfig)
                                                  (From 'V6
                                                   :> (Description ""
                                                       :> (ZUser
                                                           :> (Summary "Put config for mlsE2EId"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("mlsE2EId"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (Feature
                                                                                                            MlsE2EIdConfig)
                                                                                                       :> Put
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               MlsE2EIdConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", MlsMigrationConfig)
                                                         (From 'V5
                                                          :> (Description ""
                                                              :> (ZUser
                                                                  :> (Summary
                                                                        "Get config for mlsMigration"
                                                                      :> (CanThrow OperationDenied
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mlsMigration"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          MlsMigrationConfig))))))))))))
                                                       :<|> Named
                                                              '("put", MlsMigrationConfig)
                                                              (From 'V5
                                                               :> (Description ""
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Put config for mlsMigration"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("mlsMigration"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (Feature
                                                                                                                        MlsMigrationConfig)
                                                                                                                   :> Put
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           MlsMigrationConfig))))))))))))))))
                                                      :<|> ((Named
                                                               '("get",
                                                                 EnforceFileDownloadLocationConfig)
                                                               (From 'V5
                                                                :> (Description
                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                    :> (ZUser
                                                                        :> (Summary
                                                                              "Get config for enforceFileDownloadLocation"
                                                                            :> (CanThrow
                                                                                  OperationDenied
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                EnforceFileDownloadLocationConfig))))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      EnforceFileDownloadLocationConfig)
                                                                    (From 'V5
                                                                     :> (Description
                                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Put config for enforceFileDownloadLocation"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("enforceFileDownloadLocation"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (Feature
                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                         :> Put
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 EnforceFileDownloadLocationConfig))))))))))))))))
                                                            :<|> (Named
                                                                    '("get",
                                                                      LimitedEventFanoutConfig)
                                                                    (From 'V5
                                                                     :> (Description ""
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Get config for limitedEventFanout"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("limitedEventFanout"
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     LimitedEventFanoutConfig))))))))))))
                                                                  :<|> (Named
                                                                          "get-all-feature-configs-for-user"
                                                                          (Summary
                                                                             "Gets feature configs for a user"
                                                                           :> (Description
                                                                                 "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                               :> (DescriptionOAuthScope
                                                                                     'ReadFeatureConfigs
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            AllTeamFeatures))))))))
                                                                        :<|> (Named
                                                                                "get-all-feature-configs-for-team"
                                                                                (Summary
                                                                                   "Gets feature configs for a team"
                                                                                 :> (Description
                                                                                       "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (ZLocalUser
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      AllTeamFeatures)))))))))
                                                                              :<|> ((Named
                                                                                       '("get-deprecated",
                                                                                         SearchVisibilityAvailableConfig)
                                                                                       (ZUser
                                                                                        :> (Summary
                                                                                              "[deprecated] Get config for searchVisibility"
                                                                                            :> (Until
                                                                                                  'V2
                                                                                                :> (Description
                                                                                                      "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              OperationDenied
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("search-visibility"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        SearchVisibilityAvailableConfig))))))))))))
                                                                                     :<|> (Named
                                                                                             '("put-deprecated",
                                                                                               SearchVisibilityAvailableConfig)
                                                                                             (ZUser
                                                                                              :> (Summary
                                                                                                    "[deprecated] Get config for searchVisibility"
                                                                                                  :> (Until
                                                                                                        'V2
                                                                                                      :> (Description
                                                                                                            "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    OperationDenied
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> ("teams"
                                                                                                                              :> (Capture
                                                                                                                                    "tid"
                                                                                                                                    TeamId
                                                                                                                                  :> ("features"
                                                                                                                                      :> ("search-visibility"
                                                                                                                                          :> (ReqBody
                                                                                                                                                '[JSON]
                                                                                                                                                (Feature
                                                                                                                                                   SearchVisibilityAvailableConfig)
                                                                                                                                              :> Put
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeature
                                                                                                                                                      SearchVisibilityAvailableConfig))))))))))))))
                                                                                           :<|> (Named
                                                                                                   '("get-deprecated",
                                                                                                     ValidateSAMLEmailsConfig)
                                                                                                   (ZUser
                                                                                                    :> (Summary
                                                                                                          "[deprecated] Get config for validateSAMLemails"
                                                                                                        :> (Until
                                                                                                              'V2
                                                                                                            :> (Description
                                                                                                                  "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          OperationDenied
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("validate-saml-emails"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    ValidateSAMLEmailsConfig))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("get-deprecated",
                                                                                                          DigitalSignaturesConfig)
                                                                                                        (ZUser
                                                                                                         :> (Summary
                                                                                                               "[deprecated] Get config for digitalSignatures"
                                                                                                             :> (Until
                                                                                                                   'V2
                                                                                                                 :> (Description
                                                                                                                       "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("digital-signatures"
                                                                                                                                                 :> Get
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         DigitalSignaturesConfig)))))))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              LegalholdConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature legalhold"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("legalhold"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     LegalholdConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    SSOConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature sso"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("sso"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           SSOConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          SearchVisibilityAvailableConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature searchVisibility"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("searchVisibility"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 SearchVisibilityAvailableConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                ValidateSAMLEmailsConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("validateSAMLemails"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       ValidateSAMLEmailsConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      DigitalSignaturesConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("digitalSignatures"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             DigitalSignaturesConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            AppLockConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature appLock"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("appLock"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   AppLockConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  FileSharingConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("fileSharing"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         FileSharingConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        ClassifiedDomainsConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("classifiedDomains"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               ClassifiedDomainsConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              ConferenceCallingConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("conferenceCalling"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     ConferenceCallingConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    SelfDeletingMessagesConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("selfDeletingMessages"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           SelfDeletingMessagesConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          GuestLinksConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 GuestLinksConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                            :<|> Named
                                                                                                                                                                   '("get-config",
                                                                                                                                                                     MLSConfig)
                                                                                                                                                                   (Summary
                                                                                                                                                                      "[deprecated] Get feature config for feature mls"
                                                                                                                                                                    :> (Until
                                                                                                                                                                          'V2
                                                                                                                                                                        :> (Description
                                                                                                                                                                              "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                            :> (ZUser
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                            :> ("feature-configs"
                                                                                                                                                                                                :> ("mls"
                                                                                                                                                                                                    :> Get
                                                                                                                                                                                                         '[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
         '("get", GuestLinksConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for conversationGuestLinks"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("conversationGuestLinks"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature GuestLinksConfig)))))))))))
       :<|> Named
              '("put", GuestLinksConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for conversationGuestLinks"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("conversationGuestLinks"
                                                           :> (ReqBody
                                                                 '[JSON] (Feature GuestLinksConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       GuestLinksConfig)))))))))))))))
      :<|> ((Named
               '("get", SndFactorPasswordChallengeConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for sndFactorPasswordChallenge"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("sndFactorPasswordChallenge"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            SndFactorPasswordChallengeConfig)))))))))))
             :<|> Named
                    '("put", SndFactorPasswordChallengeConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for sndFactorPasswordChallenge"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("sndFactorPasswordChallenge"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          SndFactorPasswordChallengeConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             SndFactorPasswordChallengeConfig)))))))))))))))
            :<|> ((Named
                     '("get", MLSConfig)
                     (From 'V5
                      :> (Description ""
                          :> (ZUser
                              :> (Summary "Get config for mls"
                                  :> (CanThrow OperationDenied
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mls"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      MLSConfig))))))))))))
                   :<|> Named
                          '("put", MLSConfig)
                          (From 'V5
                           :> (Description ""
                               :> (ZUser
                                   :> (Summary "Put config for mls"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("mls"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (Feature MLSConfig)
                                                                               :> Put
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       MLSConfig))))))))))))))))
                  :<|> ((Named
                           '("get", ExposeInvitationURLsToTeamAdminConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("exposeInvitationURLsToTeamAdmin"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        ExposeInvitationURLsToTeamAdminConfig)))))))))))
                         :<|> Named
                                '("put", ExposeInvitationURLsToTeamAdminConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("exposeInvitationURLsToTeamAdmin"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      ExposeInvitationURLsToTeamAdminConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", SearchVisibilityInboundConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for searchVisibilityInbound"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("searchVisibilityInbound"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              SearchVisibilityInboundConfig)))))))))))
                               :<|> Named
                                      '("put", SearchVisibilityInboundConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for searchVisibilityInbound"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("searchVisibilityInbound"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            SearchVisibilityInboundConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               SearchVisibilityInboundConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", OutlookCalIntegrationConfig)
                                       (Description ""
                                        :> (ZUser
                                            :> (Summary "Get config for outlookCalIntegration"
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("teams"
                                                                :> (Capture "tid" TeamId
                                                                    :> ("features"
                                                                        :> ("outlookCalIntegration"
                                                                            :> Get
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    OutlookCalIntegrationConfig)))))))))))
                                     :<|> Named
                                            '("put", OutlookCalIntegrationConfig)
                                            (Description ""
                                             :> (ZUser
                                                 :> (Summary "Put config for outlookCalIntegration"
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow 'TeamNotFound
                                                                 :> (CanThrow TeamFeatureError
                                                                     :> (CanThrowMany '[]
                                                                         :> ("teams"
                                                                             :> (Capture
                                                                                   "tid" TeamId
                                                                                 :> ("features"
                                                                                     :> ("outlookCalIntegration"
                                                                                         :> (ReqBody
                                                                                               '[JSON]
                                                                                               (Feature
                                                                                                  OutlookCalIntegrationConfig)
                                                                                             :> Put
                                                                                                  '[JSON]
                                                                                                  (LockableFeature
                                                                                                     OutlookCalIntegrationConfig)))))))))))))))
                                    :<|> (Named
                                            '("get", MlsE2EIdConfig)
                                            (From 'V5
                                             :> (Description ""
                                                 :> (ZUser
                                                     :> (Summary "Get config for mlsE2EId"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("mlsE2EId"
                                                                                     :> Get
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             MlsE2EIdConfig))))))))))))
                                          :<|> (Named
                                                  "put-MlsE2EIdConfig@v5"
                                                  (From 'V5
                                                   :> (Until 'V6
                                                       :> (ZUser
                                                           :> (Summary "Put config for mlsE2EId"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("mlsE2EId"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (Feature
                                                                                                            MlsE2EIdConfig)
                                                                                                       :> Put
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               MlsE2EIdConfig)))))))))))))))
                                                :<|> (Named
                                                        '("put", MlsE2EIdConfig)
                                                        (From 'V6
                                                         :> (Description ""
                                                             :> (ZUser
                                                                 :> (Summary
                                                                       "Put config for mlsE2EId"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("mlsE2EId"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (Feature
                                                                                                                  MlsE2EIdConfig)
                                                                                                             :> Put
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     MlsE2EIdConfig)))))))))))))))
                                                      :<|> ((Named
                                                               '("get", MlsMigrationConfig)
                                                               (From 'V5
                                                                :> (Description ""
                                                                    :> (ZUser
                                                                        :> (Summary
                                                                              "Get config for mlsMigration"
                                                                            :> (CanThrow
                                                                                  OperationDenied
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("mlsMigration"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                MlsMigrationConfig))))))))))))
                                                             :<|> Named
                                                                    '("put", MlsMigrationConfig)
                                                                    (From 'V5
                                                                     :> (Description ""
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Put config for mlsMigration"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("mlsMigration"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (Feature
                                                                                                                              MlsMigrationConfig)
                                                                                                                         :> Put
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 MlsMigrationConfig))))))))))))))))
                                                            :<|> ((Named
                                                                     '("get",
                                                                       EnforceFileDownloadLocationConfig)
                                                                     (From 'V5
                                                                      :> (Description
                                                                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                          :> (ZUser
                                                                              :> (Summary
                                                                                    "Get config for enforceFileDownloadLocation"
                                                                                  :> (CanThrow
                                                                                        OperationDenied
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("enforceFileDownloadLocation"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      EnforceFileDownloadLocationConfig))))))))))))
                                                                   :<|> Named
                                                                          '("put",
                                                                            EnforceFileDownloadLocationConfig)
                                                                          (From 'V5
                                                                           :> (Description
                                                                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Put config for enforceFileDownloadLocation"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> (CanThrow
                                                                                                         TeamFeatureError
                                                                                                       :> (CanThrowMany
                                                                                                             '[]
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> ("enforceFileDownloadLocation"
                                                                                                                           :> (ReqBody
                                                                                                                                 '[JSON]
                                                                                                                                 (Feature
                                                                                                                                    EnforceFileDownloadLocationConfig)
                                                                                                                               :> Put
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       EnforceFileDownloadLocationConfig))))))))))))))))
                                                                  :<|> (Named
                                                                          '("get",
                                                                            LimitedEventFanoutConfig)
                                                                          (From 'V5
                                                                           :> (Description ""
                                                                               :> (ZUser
                                                                                   :> (Summary
                                                                                         "Get config for limitedEventFanout"
                                                                                       :> (CanThrow
                                                                                             OperationDenied
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("limitedEventFanout"
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           LimitedEventFanoutConfig))))))))))))
                                                                        :<|> (Named
                                                                                "get-all-feature-configs-for-user"
                                                                                (Summary
                                                                                   "Gets feature configs for a user"
                                                                                 :> (Description
                                                                                       "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                                     :> (DescriptionOAuthScope
                                                                                           'ReadFeatureConfigs
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  AllTeamFeatures))))))))
                                                                              :<|> (Named
                                                                                      "get-all-feature-configs-for-team"
                                                                                      (Summary
                                                                                         "Gets feature configs for a team"
                                                                                       :> (Description
                                                                                             "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                           :> (CanThrow
                                                                                                 'NotATeamMember
                                                                                               :> (CanThrow
                                                                                                     OperationDenied
                                                                                                   :> (CanThrow
                                                                                                         'TeamNotFound
                                                                                                       :> (ZLocalUser
                                                                                                           :> ("teams"
                                                                                                               :> (Capture
                                                                                                                     "tid"
                                                                                                                     TeamId
                                                                                                                   :> ("features"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            AllTeamFeatures)))))))))
                                                                                    :<|> ((Named
                                                                                             '("get-deprecated",
                                                                                               SearchVisibilityAvailableConfig)
                                                                                             (ZUser
                                                                                              :> (Summary
                                                                                                    "[deprecated] Get config for searchVisibility"
                                                                                                  :> (Until
                                                                                                        'V2
                                                                                                      :> (Description
                                                                                                            "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    OperationDenied
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("search-visibility"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              SearchVisibilityAvailableConfig))))))))))))
                                                                                           :<|> (Named
                                                                                                   '("put-deprecated",
                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                   (ZUser
                                                                                                    :> (Summary
                                                                                                          "[deprecated] Get config for searchVisibility"
                                                                                                        :> (Until
                                                                                                              'V2
                                                                                                            :> (Description
                                                                                                                  "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          OperationDenied
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> (CanThrow
                                                                                                                                  TeamFeatureError
                                                                                                                                :> ("teams"
                                                                                                                                    :> (Capture
                                                                                                                                          "tid"
                                                                                                                                          TeamId
                                                                                                                                        :> ("features"
                                                                                                                                            :> ("search-visibility"
                                                                                                                                                :> (ReqBody
                                                                                                                                                      '[JSON]
                                                                                                                                                      (Feature
                                                                                                                                                         SearchVisibilityAvailableConfig)
                                                                                                                                                    :> Put
                                                                                                                                                         '[JSON]
                                                                                                                                                         (LockableFeature
                                                                                                                                                            SearchVisibilityAvailableConfig))))))))))))))
                                                                                                 :<|> (Named
                                                                                                         '("get-deprecated",
                                                                                                           ValidateSAMLEmailsConfig)
                                                                                                         (ZUser
                                                                                                          :> (Summary
                                                                                                                "[deprecated] Get config for validateSAMLemails"
                                                                                                              :> (Until
                                                                                                                    'V2
                                                                                                                  :> (Description
                                                                                                                        "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                      :> (CanThrow
                                                                                                                            'NotATeamMember
                                                                                                                          :> (CanThrow
                                                                                                                                OperationDenied
                                                                                                                              :> (CanThrow
                                                                                                                                    'TeamNotFound
                                                                                                                                  :> ("teams"
                                                                                                                                      :> (Capture
                                                                                                                                            "tid"
                                                                                                                                            TeamId
                                                                                                                                          :> ("features"
                                                                                                                                              :> ("validate-saml-emails"
                                                                                                                                                  :> Get
                                                                                                                                                       '[JSON]
                                                                                                                                                       (LockableFeature
                                                                                                                                                          ValidateSAMLEmailsConfig))))))))))))
                                                                                                       :<|> Named
                                                                                                              '("get-deprecated",
                                                                                                                DigitalSignaturesConfig)
                                                                                                              (ZUser
                                                                                                               :> (Summary
                                                                                                                     "[deprecated] Get config for digitalSignatures"
                                                                                                                   :> (Until
                                                                                                                         'V2
                                                                                                                       :> (Description
                                                                                                                             "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("teams"
                                                                                                                                           :> (Capture
                                                                                                                                                 "tid"
                                                                                                                                                 TeamId
                                                                                                                                               :> ("features"
                                                                                                                                                   :> ("digital-signatures"
                                                                                                                                                       :> Get
                                                                                                                                                            '[JSON]
                                                                                                                                                            (LockableFeature
                                                                                                                                                               DigitalSignaturesConfig)))))))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    LegalholdConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature legalhold"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("legalhold"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           LegalholdConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          SSOConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature sso"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("sso"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 SSOConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                SearchVisibilityAvailableConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature searchVisibility"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("searchVisibility"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       SearchVisibilityAvailableConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      ValidateSAMLEmailsConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("validateSAMLemails"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             ValidateSAMLEmailsConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            DigitalSignaturesConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("digitalSignatures"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   DigitalSignaturesConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  AppLockConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature appLock"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("appLock"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         AppLockConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        FileSharingConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("fileSharing"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               FileSharingConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              ClassifiedDomainsConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("classifiedDomains"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     ClassifiedDomainsConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    ConferenceCallingConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("conferenceCalling"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           ConferenceCallingConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          SelfDeletingMessagesConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("selfDeletingMessages"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 SelfDeletingMessagesConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                GuestLinksConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       GuestLinksConfig))))))))))
                                                                                                                                                            :<|> (Named
                                                                                                                                                                    '("get-config",
                                                                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                                                                    (Summary
                                                                                                                                                                       "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                                     :> (Until
                                                                                                                                                                           'V2
                                                                                                                                                                         :> (Description
                                                                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                             :> (ZUser
                                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                                       'NotATeamMember
                                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                                           OperationDenied
                                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                                               'TeamNotFound
                                                                                                                                                                                             :> ("feature-configs"
                                                                                                                                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                                     :> Get
                                                                                                                                                                                                          '[JSON]
                                                                                                                                                                                                          (LockableFeature
                                                                                                                                                                                                             SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                                  :<|> Named
                                                                                                                                                                         '("get-config",
                                                                                                                                                                           MLSConfig)
                                                                                                                                                                         (Summary
                                                                                                                                                                            "[deprecated] Get feature config for feature mls"
                                                                                                                                                                          :> (Until
                                                                                                                                                                                'V2
                                                                                                                                                                              :> (Description
                                                                                                                                                                                    "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                                  :> (ZUser
                                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                                            'NotATeamMember
                                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                                OperationDenied
                                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                                    'TeamNotFound
                                                                                                                                                                                                  :> ("feature-configs"
                                                                                                                                                                                                      :> ("mls"
                                                                                                                                                                                                          :> Get
                                                                                                                                                                                                               '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     '("get", SndFactorPasswordChallengeConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for sndFactorPasswordChallenge"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("sndFactorPasswordChallenge"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SndFactorPasswordChallengeConfig)))))))))))
   :<|> Named
          '("put", SndFactorPasswordChallengeConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for sndFactorPasswordChallenge"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("sndFactorPasswordChallenge"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature
                                                                SndFactorPasswordChallengeConfig)
                                                           :> Put
                                                                '[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
     '("get", SndFactorPasswordChallengeConfig)
     (Description (FeatureAPIDesc SndFactorPasswordChallengeConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol
                   "Get config for " (FeatureSymbol SndFactorPasswordChallengeConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol SndFactorPasswordChallengeConfig
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SndFactorPasswordChallengeConfig)))))))))))
   :<|> Named
          '("put", SndFactorPasswordChallengeConfig)
          (Description (FeatureAPIDesc SndFactorPasswordChallengeConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol
                        "Put config for " (FeatureSymbol SndFactorPasswordChallengeConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors SndFactorPasswordChallengeConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol
                                                         SndFactorPasswordChallengeConfig
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature
                                                                SndFactorPasswordChallengeConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", SndFactorPasswordChallengeConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for sndFactorPasswordChallenge"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("sndFactorPasswordChallenge"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SndFactorPasswordChallengeConfig)))))))))))
   :<|> Named
          '("put", SndFactorPasswordChallengeConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for sndFactorPasswordChallenge"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("sndFactorPasswordChallenge"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature
                                                                SndFactorPasswordChallengeConfig)
                                                           :> Put
                                                                '[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
         '("get", MLSConfig)
         (From 'V5
          :> (Description ""
              :> (ZUser
                  :> (Summary "Get config for mls"
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("mls"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature MLSConfig))))))))))))
       :<|> Named
              '("put", MLSConfig)
              (From 'V5
               :> (Description ""
                   :> (ZUser
                       :> (Summary "Put config for mls"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("mls"
                                                               :> (ReqBody
                                                                     '[JSON] (Feature MLSConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           MLSConfig))))))))))))))))
      :<|> ((Named
               '("get", ExposeInvitationURLsToTeamAdminConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            ExposeInvitationURLsToTeamAdminConfig)))))))))))
             :<|> Named
                    '("put", ExposeInvitationURLsToTeamAdminConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("exposeInvitationURLsToTeamAdmin"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
            :<|> ((Named
                     '("get", SearchVisibilityInboundConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for searchVisibilityInbound"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("searchVisibilityInbound"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  SearchVisibilityInboundConfig)))))))))))
                   :<|> Named
                          '("put", SearchVisibilityInboundConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for searchVisibilityInbound"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("searchVisibilityInbound"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                SearchVisibilityInboundConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   SearchVisibilityInboundConfig)))))))))))))))
                  :<|> ((Named
                           '("get", OutlookCalIntegrationConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for outlookCalIntegration"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("outlookCalIntegration"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        OutlookCalIntegrationConfig)))))))))))
                         :<|> Named
                                '("put", OutlookCalIntegrationConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for outlookCalIntegration"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("outlookCalIntegration"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      OutlookCalIntegrationConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         OutlookCalIntegrationConfig)))))))))))))))
                        :<|> (Named
                                '("get", MlsE2EIdConfig)
                                (From 'V5
                                 :> (Description ""
                                     :> (ZUser
                                         :> (Summary "Get config for mlsE2EId"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("mlsE2EId"
                                                                         :> Get
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 MlsE2EIdConfig))))))))))))
                              :<|> (Named
                                      "put-MlsE2EIdConfig@v5"
                                      (From 'V5
                                       :> (Until 'V6
                                           :> (ZUser
                                               :> (Summary "Put config for mlsE2EId"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("mlsE2EId"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (Feature
                                                                                                MlsE2EIdConfig)
                                                                                           :> Put
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   MlsE2EIdConfig)))))))))))))))
                                    :<|> (Named
                                            '("put", MlsE2EIdConfig)
                                            (From 'V6
                                             :> (Description ""
                                                 :> (ZUser
                                                     :> (Summary "Put config for mlsE2EId"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("mlsE2EId"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (Feature
                                                                                                      MlsE2EIdConfig)
                                                                                                 :> Put
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         MlsE2EIdConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", MlsMigrationConfig)
                                                   (From 'V5
                                                    :> (Description ""
                                                        :> (ZUser
                                                            :> (Summary
                                                                  "Get config for mlsMigration"
                                                                :> (CanThrow OperationDenied
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mlsMigration"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    MlsMigrationConfig))))))))))))
                                                 :<|> Named
                                                        '("put", MlsMigrationConfig)
                                                        (From 'V5
                                                         :> (Description ""
                                                             :> (ZUser
                                                                 :> (Summary
                                                                       "Put config for mlsMigration"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("mlsMigration"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (Feature
                                                                                                                  MlsMigrationConfig)
                                                                                                             :> Put
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     MlsMigrationConfig))))))))))))))))
                                                :<|> ((Named
                                                         '("get", EnforceFileDownloadLocationConfig)
                                                         (From 'V5
                                                          :> (Description
                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                              :> (ZUser
                                                                  :> (Summary
                                                                        "Get config for enforceFileDownloadLocation"
                                                                      :> (CanThrow OperationDenied
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          EnforceFileDownloadLocationConfig))))))))))))
                                                       :<|> Named
                                                              '("put",
                                                                EnforceFileDownloadLocationConfig)
                                                              (From 'V5
                                                               :> (Description
                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Put config for enforceFileDownloadLocation"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("enforceFileDownloadLocation"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (Feature
                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                   :> Put
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           EnforceFileDownloadLocationConfig))))))))))))))))
                                                      :<|> (Named
                                                              '("get", LimitedEventFanoutConfig)
                                                              (From 'V5
                                                               :> (Description ""
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Get config for limitedEventFanout"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("limitedEventFanout"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               LimitedEventFanoutConfig))))))))))))
                                                            :<|> (Named
                                                                    "get-all-feature-configs-for-user"
                                                                    (Summary
                                                                       "Gets feature configs for a user"
                                                                     :> (Description
                                                                           "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                         :> (DescriptionOAuthScope
                                                                               'ReadFeatureConfigs
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      AllTeamFeatures))))))))
                                                                  :<|> (Named
                                                                          "get-all-feature-configs-for-team"
                                                                          (Summary
                                                                             "Gets feature configs for a team"
                                                                           :> (Description
                                                                                 "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (ZLocalUser
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                AllTeamFeatures)))))))))
                                                                        :<|> ((Named
                                                                                 '("get-deprecated",
                                                                                   SearchVisibilityAvailableConfig)
                                                                                 (ZUser
                                                                                  :> (Summary
                                                                                        "[deprecated] Get config for searchVisibility"
                                                                                      :> (Until 'V2
                                                                                          :> (Description
                                                                                                "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        OperationDenied
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("search-visibility"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SearchVisibilityAvailableConfig))))))))))))
                                                                               :<|> (Named
                                                                                       '("put-deprecated",
                                                                                         SearchVisibilityAvailableConfig)
                                                                                       (ZUser
                                                                                        :> (Summary
                                                                                              "[deprecated] Get config for searchVisibility"
                                                                                            :> (Until
                                                                                                  'V2
                                                                                                :> (Description
                                                                                                      "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              OperationDenied
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> ("teams"
                                                                                                                        :> (Capture
                                                                                                                              "tid"
                                                                                                                              TeamId
                                                                                                                            :> ("features"
                                                                                                                                :> ("search-visibility"
                                                                                                                                    :> (ReqBody
                                                                                                                                          '[JSON]
                                                                                                                                          (Feature
                                                                                                                                             SearchVisibilityAvailableConfig)
                                                                                                                                        :> Put
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeature
                                                                                                                                                SearchVisibilityAvailableConfig))))))))))))))
                                                                                     :<|> (Named
                                                                                             '("get-deprecated",
                                                                                               ValidateSAMLEmailsConfig)
                                                                                             (ZUser
                                                                                              :> (Summary
                                                                                                    "[deprecated] Get config for validateSAMLemails"
                                                                                                  :> (Until
                                                                                                        'V2
                                                                                                      :> (Description
                                                                                                            "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    OperationDenied
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("validate-saml-emails"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              ValidateSAMLEmailsConfig))))))))))))
                                                                                           :<|> Named
                                                                                                  '("get-deprecated",
                                                                                                    DigitalSignaturesConfig)
                                                                                                  (ZUser
                                                                                                   :> (Summary
                                                                                                         "[deprecated] Get config for digitalSignatures"
                                                                                                       :> (Until
                                                                                                             'V2
                                                                                                           :> (Description
                                                                                                                 "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("digital-signatures"
                                                                                                                                           :> Get
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   DigitalSignaturesConfig)))))))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        LegalholdConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature legalhold"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("legalhold"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               LegalholdConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              SSOConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature sso"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("sso"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     SSOConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    SearchVisibilityAvailableConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature searchVisibility"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("searchVisibility"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           SearchVisibilityAvailableConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          ValidateSAMLEmailsConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("validateSAMLemails"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 ValidateSAMLEmailsConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                DigitalSignaturesConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("digitalSignatures"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       DigitalSignaturesConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      AppLockConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature appLock"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("appLock"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             AppLockConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            FileSharingConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature fileSharing"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("fileSharing"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   FileSharingConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  ClassifiedDomainsConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("classifiedDomains"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         ClassifiedDomainsConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        ConferenceCallingConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("conferenceCalling"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               ConferenceCallingConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              SelfDeletingMessagesConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("selfDeletingMessages"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     SelfDeletingMessagesConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    GuestLinksConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           GuestLinksConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                      :<|> Named
                                                                                                                                                             '("get-config",
                                                                                                                                                               MLSConfig)
                                                                                                                                                             (Summary
                                                                                                                                                                "[deprecated] Get feature config for feature mls"
                                                                                                                                                              :> (Until
                                                                                                                                                                    'V2
                                                                                                                                                                  :> (Description
                                                                                                                                                                        "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                      :> (ZUser
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                      :> ("feature-configs"
                                                                                                                                                                                          :> ("mls"
                                                                                                                                                                                              :> Get
                                                                                                                                                                                                   '[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
         '("get", SndFactorPasswordChallengeConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for sndFactorPasswordChallenge"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("sndFactorPasswordChallenge"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      SndFactorPasswordChallengeConfig)))))))))))
       :<|> Named
              '("put", SndFactorPasswordChallengeConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for sndFactorPasswordChallenge"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("sndFactorPasswordChallenge"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    SndFactorPasswordChallengeConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       SndFactorPasswordChallengeConfig)))))))))))))))
      :<|> ((Named
               '("get", MLSConfig)
               (From 'V5
                :> (Description ""
                    :> (ZUser
                        :> (Summary "Get config for mls"
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("mls"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature MLSConfig))))))))))))
             :<|> Named
                    '("put", MLSConfig)
                    (From 'V5
                     :> (Description ""
                         :> (ZUser
                             :> (Summary "Put config for mls"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany '[]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("mls"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (Feature MLSConfig)
                                                                         :> Put
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 MLSConfig))))))))))))))))
            :<|> ((Named
                     '("get", ExposeInvitationURLsToTeamAdminConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("exposeInvitationURLsToTeamAdmin"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  ExposeInvitationURLsToTeamAdminConfig)))))))))))
                   :<|> Named
                          '("put", ExposeInvitationURLsToTeamAdminConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("exposeInvitationURLsToTeamAdmin"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
                  :<|> ((Named
                           '("get", SearchVisibilityInboundConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for searchVisibilityInbound"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("searchVisibilityInbound"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        SearchVisibilityInboundConfig)))))))))))
                         :<|> Named
                                '("put", SearchVisibilityInboundConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for searchVisibilityInbound"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("searchVisibilityInbound"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      SearchVisibilityInboundConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         SearchVisibilityInboundConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", OutlookCalIntegrationConfig)
                                 (Description ""
                                  :> (ZUser
                                      :> (Summary "Get config for outlookCalIntegration"
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("teams"
                                                          :> (Capture "tid" TeamId
                                                              :> ("features"
                                                                  :> ("outlookCalIntegration"
                                                                      :> Get
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              OutlookCalIntegrationConfig)))))))))))
                               :<|> Named
                                      '("put", OutlookCalIntegrationConfig)
                                      (Description ""
                                       :> (ZUser
                                           :> (Summary "Put config for outlookCalIntegration"
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow 'TeamNotFound
                                                           :> (CanThrow TeamFeatureError
                                                               :> (CanThrowMany '[]
                                                                   :> ("teams"
                                                                       :> (Capture "tid" TeamId
                                                                           :> ("features"
                                                                               :> ("outlookCalIntegration"
                                                                                   :> (ReqBody
                                                                                         '[JSON]
                                                                                         (Feature
                                                                                            OutlookCalIntegrationConfig)
                                                                                       :> Put
                                                                                            '[JSON]
                                                                                            (LockableFeature
                                                                                               OutlookCalIntegrationConfig)))))))))))))))
                              :<|> (Named
                                      '("get", MlsE2EIdConfig)
                                      (From 'V5
                                       :> (Description ""
                                           :> (ZUser
                                               :> (Summary "Get config for mlsE2EId"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("mlsE2EId"
                                                                               :> Get
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       MlsE2EIdConfig))))))))))))
                                    :<|> (Named
                                            "put-MlsE2EIdConfig@v5"
                                            (From 'V5
                                             :> (Until 'V6
                                                 :> (ZUser
                                                     :> (Summary "Put config for mlsE2EId"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("mlsE2EId"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (Feature
                                                                                                      MlsE2EIdConfig)
                                                                                                 :> Put
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         MlsE2EIdConfig)))))))))))))))
                                          :<|> (Named
                                                  '("put", MlsE2EIdConfig)
                                                  (From 'V6
                                                   :> (Description ""
                                                       :> (ZUser
                                                           :> (Summary "Put config for mlsE2EId"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("mlsE2EId"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (Feature
                                                                                                            MlsE2EIdConfig)
                                                                                                       :> Put
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               MlsE2EIdConfig)))))))))))))))
                                                :<|> ((Named
                                                         '("get", MlsMigrationConfig)
                                                         (From 'V5
                                                          :> (Description ""
                                                              :> (ZUser
                                                                  :> (Summary
                                                                        "Get config for mlsMigration"
                                                                      :> (CanThrow OperationDenied
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("mlsMigration"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          MlsMigrationConfig))))))))))))
                                                       :<|> Named
                                                              '("put", MlsMigrationConfig)
                                                              (From 'V5
                                                               :> (Description ""
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Put config for mlsMigration"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("mlsMigration"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (Feature
                                                                                                                        MlsMigrationConfig)
                                                                                                                   :> Put
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           MlsMigrationConfig))))))))))))))))
                                                      :<|> ((Named
                                                               '("get",
                                                                 EnforceFileDownloadLocationConfig)
                                                               (From 'V5
                                                                :> (Description
                                                                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                    :> (ZUser
                                                                        :> (Summary
                                                                              "Get config for enforceFileDownloadLocation"
                                                                            :> (CanThrow
                                                                                  OperationDenied
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("enforceFileDownloadLocation"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                EnforceFileDownloadLocationConfig))))))))))))
                                                             :<|> Named
                                                                    '("put",
                                                                      EnforceFileDownloadLocationConfig)
                                                                    (From 'V5
                                                                     :> (Description
                                                                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Put config for enforceFileDownloadLocation"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> (CanThrow
                                                                                                   TeamFeatureError
                                                                                                 :> (CanThrowMany
                                                                                                       '[]
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> ("enforceFileDownloadLocation"
                                                                                                                     :> (ReqBody
                                                                                                                           '[JSON]
                                                                                                                           (Feature
                                                                                                                              EnforceFileDownloadLocationConfig)
                                                                                                                         :> Put
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 EnforceFileDownloadLocationConfig))))))))))))))))
                                                            :<|> (Named
                                                                    '("get",
                                                                      LimitedEventFanoutConfig)
                                                                    (From 'V5
                                                                     :> (Description ""
                                                                         :> (ZUser
                                                                             :> (Summary
                                                                                   "Get config for limitedEventFanout"
                                                                                 :> (CanThrow
                                                                                       OperationDenied
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("limitedEventFanout"
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     LimitedEventFanoutConfig))))))))))))
                                                                  :<|> (Named
                                                                          "get-all-feature-configs-for-user"
                                                                          (Summary
                                                                             "Gets feature configs for a user"
                                                                           :> (Description
                                                                                 "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                               :> (DescriptionOAuthScope
                                                                                     'ReadFeatureConfigs
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            AllTeamFeatures))))))))
                                                                        :<|> (Named
                                                                                "get-all-feature-configs-for-team"
                                                                                (Summary
                                                                                   "Gets feature configs for a team"
                                                                                 :> (Description
                                                                                       "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                                     :> (CanThrow
                                                                                           'NotATeamMember
                                                                                         :> (CanThrow
                                                                                               OperationDenied
                                                                                             :> (CanThrow
                                                                                                   'TeamNotFound
                                                                                                 :> (ZLocalUser
                                                                                                     :> ("teams"
                                                                                                         :> (Capture
                                                                                                               "tid"
                                                                                                               TeamId
                                                                                                             :> ("features"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      AllTeamFeatures)))))))))
                                                                              :<|> ((Named
                                                                                       '("get-deprecated",
                                                                                         SearchVisibilityAvailableConfig)
                                                                                       (ZUser
                                                                                        :> (Summary
                                                                                              "[deprecated] Get config for searchVisibility"
                                                                                            :> (Until
                                                                                                  'V2
                                                                                                :> (Description
                                                                                                      "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              OperationDenied
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("search-visibility"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        SearchVisibilityAvailableConfig))))))))))))
                                                                                     :<|> (Named
                                                                                             '("put-deprecated",
                                                                                               SearchVisibilityAvailableConfig)
                                                                                             (ZUser
                                                                                              :> (Summary
                                                                                                    "[deprecated] Get config for searchVisibility"
                                                                                                  :> (Until
                                                                                                        'V2
                                                                                                      :> (Description
                                                                                                            "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    OperationDenied
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> (CanThrow
                                                                                                                            TeamFeatureError
                                                                                                                          :> ("teams"
                                                                                                                              :> (Capture
                                                                                                                                    "tid"
                                                                                                                                    TeamId
                                                                                                                                  :> ("features"
                                                                                                                                      :> ("search-visibility"
                                                                                                                                          :> (ReqBody
                                                                                                                                                '[JSON]
                                                                                                                                                (Feature
                                                                                                                                                   SearchVisibilityAvailableConfig)
                                                                                                                                              :> Put
                                                                                                                                                   '[JSON]
                                                                                                                                                   (LockableFeature
                                                                                                                                                      SearchVisibilityAvailableConfig))))))))))))))
                                                                                           :<|> (Named
                                                                                                   '("get-deprecated",
                                                                                                     ValidateSAMLEmailsConfig)
                                                                                                   (ZUser
                                                                                                    :> (Summary
                                                                                                          "[deprecated] Get config for validateSAMLemails"
                                                                                                        :> (Until
                                                                                                              'V2
                                                                                                            :> (Description
                                                                                                                  "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                                :> (CanThrow
                                                                                                                      'NotATeamMember
                                                                                                                    :> (CanThrow
                                                                                                                          OperationDenied
                                                                                                                        :> (CanThrow
                                                                                                                              'TeamNotFound
                                                                                                                            :> ("teams"
                                                                                                                                :> (Capture
                                                                                                                                      "tid"
                                                                                                                                      TeamId
                                                                                                                                    :> ("features"
                                                                                                                                        :> ("validate-saml-emails"
                                                                                                                                            :> Get
                                                                                                                                                 '[JSON]
                                                                                                                                                 (LockableFeature
                                                                                                                                                    ValidateSAMLEmailsConfig))))))))))))
                                                                                                 :<|> Named
                                                                                                        '("get-deprecated",
                                                                                                          DigitalSignaturesConfig)
                                                                                                        (ZUser
                                                                                                         :> (Summary
                                                                                                               "[deprecated] Get config for digitalSignatures"
                                                                                                             :> (Until
                                                                                                                   'V2
                                                                                                                 :> (Description
                                                                                                                       "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("teams"
                                                                                                                                     :> (Capture
                                                                                                                                           "tid"
                                                                                                                                           TeamId
                                                                                                                                         :> ("features"
                                                                                                                                             :> ("digital-signatures"
                                                                                                                                                 :> Get
                                                                                                                                                      '[JSON]
                                                                                                                                                      (LockableFeature
                                                                                                                                                         DigitalSignaturesConfig)))))))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              LegalholdConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature legalhold"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("legalhold"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     LegalholdConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    SSOConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature sso"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("sso"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           SSOConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          SearchVisibilityAvailableConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature searchVisibility"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("searchVisibility"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 SearchVisibilityAvailableConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                ValidateSAMLEmailsConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("validateSAMLemails"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       ValidateSAMLEmailsConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      DigitalSignaturesConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("digitalSignatures"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             DigitalSignaturesConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            AppLockConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature appLock"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("appLock"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   AppLockConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  FileSharingConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature fileSharing"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("fileSharing"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         FileSharingConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        ClassifiedDomainsConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("classifiedDomains"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               ClassifiedDomainsConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              ConferenceCallingConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("conferenceCalling"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     ConferenceCallingConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    SelfDeletingMessagesConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("selfDeletingMessages"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           SelfDeletingMessagesConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          GuestLinksConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 GuestLinksConfig))))))))))
                                                                                                                                                      :<|> (Named
                                                                                                                                                              '("get-config",
                                                                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                                                                              (Summary
                                                                                                                                                                 "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                               :> (Until
                                                                                                                                                                     'V2
                                                                                                                                                                   :> (Description
                                                                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                       :> (ZUser
                                                                                                                                                                           :> (CanThrow
                                                                                                                                                                                 'NotATeamMember
                                                                                                                                                                               :> (CanThrow
                                                                                                                                                                                     OperationDenied
                                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                                         'TeamNotFound
                                                                                                                                                                                       :> ("feature-configs"
                                                                                                                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                               :> Get
                                                                                                                                                                                                    '[JSON]
                                                                                                                                                                                                    (LockableFeature
                                                                                                                                                                                                       SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                            :<|> Named
                                                                                                                                                                   '("get-config",
                                                                                                                                                                     MLSConfig)
                                                                                                                                                                   (Summary
                                                                                                                                                                      "[deprecated] Get feature config for feature mls"
                                                                                                                                                                    :> (Until
                                                                                                                                                                          'V2
                                                                                                                                                                        :> (Description
                                                                                                                                                                              "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                            :> (ZUser
                                                                                                                                                                                :> (CanThrow
                                                                                                                                                                                      'NotATeamMember
                                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                                          OperationDenied
                                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                                              'TeamNotFound
                                                                                                                                                                                            :> ("feature-configs"
                                                                                                                                                                                                :> ("mls"
                                                                                                                                                                                                    :> Get
                                                                                                                                                                                                         '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> (ServerT
   (Named
      '("get", MLSConfig)
      (Description (FeatureAPIDesc MLSConfig)
       :> (ZUser
           :> (Summary
                 (AppendSymbol "Get config for " (FeatureSymbol MLSConfig))
               :> (CanThrow OperationDenied
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> (FeatureSymbol MLSConfig
                                           :> Get '[JSON] (LockableFeature MLSConfig)))))))))))
    :<|> Named
           '("put", MLSConfig)
           (Description (FeatureAPIDesc MLSConfig)
            :> (ZUser
                :> (Summary
                      (AppendSymbol "Put config for " (FeatureSymbol MLSConfig))
                    :> (CanThrow OperationDenied
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany (FeatureErrors MLSConfig)
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> (FeatureSymbol MLSConfig
                                                        :> (ReqBody '[JSON] (Feature MLSConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    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])
 -> ServerT
      (Named
         '("get", MLSConfig)
         (From 'V5
          :> (Description ""
              :> (ZUser
                  :> (Summary "Get config for mls"
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("mls"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature MLSConfig))))))))))))
       :<|> Named
              '("put", MLSConfig)
              (From 'V5
               :> (Description ""
                   :> (ZUser
                       :> (Summary "Put config for mls"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("mls"
                                                               :> (ReqBody
                                                                     '[JSON] (Feature MLSConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           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]))
-> API
     (Named
        '("get", MLSConfig)
        (Description (FeatureAPIDesc MLSConfig)
         :> (ZUser
             :> (Summary
                   (AppendSymbol "Get config for " (FeatureSymbol MLSConfig))
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> (FeatureSymbol MLSConfig
                                             :> Get '[JSON] (LockableFeature MLSConfig)))))))))))
      :<|> Named
             '("put", MLSConfig)
             (Description (FeatureAPIDesc MLSConfig)
              :> (ZUser
                  :> (Summary
                        (AppendSymbol "Put config for " (FeatureSymbol MLSConfig))
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> (CanThrow TeamFeatureError
                                      :> (CanThrowMany (FeatureErrors MLSConfig)
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> (FeatureSymbol MLSConfig
                                                          :> (ReqBody '[JSON] (Feature MLSConfig)
                                                              :> Put
                                                                   '[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
        '("get", MLSConfig)
        (From 'V5
         :> (Description ""
             :> (ZUser
                 :> (Summary "Get config for mls"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("mls"
                                                 :> Get
                                                      '[JSON] (LockableFeature MLSConfig))))))))))))
      :<|> Named
             '("put", MLSConfig)
             (From 'V5
              :> (Description ""
                  :> (ZUser
                      :> (Summary "Put config for mls"
                          :> (CanThrow OperationDenied
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mls"
                                                              :> (ReqBody
                                                                    '[JSON] (Feature MLSConfig)
                                                                  :> Put
                                                                       '[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 {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
  (Named
     '("get", MLSConfig)
     (Description (FeatureAPIDesc MLSConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol "Get config for " (FeatureSymbol MLSConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol MLSConfig
                                          :> Get '[JSON] (LockableFeature MLSConfig)))))))))))
   :<|> Named
          '("put", MLSConfig)
          (Description (FeatureAPIDesc MLSConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol "Put config for " (FeatureSymbol MLSConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors MLSConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol MLSConfig
                                                       :> (ReqBody '[JSON] (Feature MLSConfig)
                                                           :> Put
                                                                '[JSON]
                                                                (LockableFeature
                                                                   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])
-> ServerT
     (Named
        '("get", MLSConfig)
        (Description (FeatureAPIDesc MLSConfig)
         :> (ZUser
             :> (Summary
                   (AppendSymbol "Get config for " (FeatureSymbol MLSConfig))
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> (FeatureSymbol MLSConfig
                                             :> Get '[JSON] (LockableFeature MLSConfig)))))))))))
      :<|> Named
             '("put", MLSConfig)
             (Description (FeatureAPIDesc MLSConfig)
              :> (ZUser
                  :> (Summary
                        (AppendSymbol "Put config for " (FeatureSymbol MLSConfig))
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> (CanThrow TeamFeatureError
                                      :> (CanThrowMany (FeatureErrors MLSConfig)
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> (FeatureSymbol MLSConfig
                                                          :> (ReqBody '[JSON] (Feature MLSConfig)
                                                              :> Put
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      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])
ServerT
  (Named
     '("get", MLSConfig)
     (Description (FeatureAPIDesc MLSConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol "Get config for " (FeatureSymbol MLSConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol MLSConfig
                                          :> Get '[JSON] (LockableFeature MLSConfig)))))))))))
   :<|> Named
          '("put", MLSConfig)
          (Description (FeatureAPIDesc MLSConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol "Put config for " (FeatureSymbol MLSConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors MLSConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol MLSConfig
                                                       :> (ReqBody '[JSON] (Feature MLSConfig)
                                                           :> Put
                                                                '[JSON]
                                                                (LockableFeature
                                                                   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])
-> ServerT
     (Named
        '("get", MLSConfig)
        (From 'V5
         :> (Description ""
             :> (ZUser
                 :> (Summary "Get config for mls"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("mls"
                                                 :> Get
                                                      '[JSON] (LockableFeature MLSConfig))))))))))))
      :<|> Named
             '("put", MLSConfig)
             (From 'V5
              :> (Description ""
                  :> (ZUser
                      :> (Summary "Put config for mls"
                          :> (CanThrow OperationDenied
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mls"
                                                              :> (ReqBody
                                                                    '[JSON] (Feature MLSConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          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])
forall a. a -> a
id API
  (Named
     '("get", MLSConfig)
     (Description (FeatureAPIDesc MLSConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol "Get config for " (FeatureSymbol MLSConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol MLSConfig
                                          :> Get '[JSON] (LockableFeature MLSConfig)))))))))))
   :<|> Named
          '("put", MLSConfig)
          (Description (FeatureAPIDesc MLSConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol "Put config for " (FeatureSymbol MLSConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors MLSConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol MLSConfig
                                                       :> (ReqBody '[JSON] (Feature MLSConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", MLSConfig)
     (From 'V5
      :> (Description ""
          :> (ZUser
              :> (Summary "Get config for mls"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("mls"
                                              :> Get '[JSON] (LockableFeature MLSConfig))))))))))))
   :<|> Named
          '("put", MLSConfig)
          (From 'V5
           :> (Description ""
               :> (ZUser
                   :> (Summary "Put config for mls"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("mls"
                                                           :> (ReqBody '[JSON] (Feature MLSConfig)
                                                               :> Put
                                                                    '[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
         '("get", ExposeInvitationURLsToTeamAdminConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("exposeInvitationURLsToTeamAdmin"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      ExposeInvitationURLsToTeamAdminConfig)))))))))))
       :<|> Named
              '("put", ExposeInvitationURLsToTeamAdminConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("exposeInvitationURLsToTeamAdmin"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
      :<|> ((Named
               '("get", SearchVisibilityInboundConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for searchVisibilityInbound"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("searchVisibilityInbound"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            SearchVisibilityInboundConfig)))))))))))
             :<|> Named
                    '("put", SearchVisibilityInboundConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for searchVisibilityInbound"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("searchVisibilityInbound"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          SearchVisibilityInboundConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             SearchVisibilityInboundConfig)))))))))))))))
            :<|> ((Named
                     '("get", OutlookCalIntegrationConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for outlookCalIntegration"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("outlookCalIntegration"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  OutlookCalIntegrationConfig)))))))))))
                   :<|> Named
                          '("put", OutlookCalIntegrationConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for outlookCalIntegration"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("outlookCalIntegration"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                OutlookCalIntegrationConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   OutlookCalIntegrationConfig)))))))))))))))
                  :<|> (Named
                          '("get", MlsE2EIdConfig)
                          (From 'V5
                           :> (Description ""
                               :> (ZUser
                                   :> (Summary "Get config for mlsE2EId"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mlsE2EId"
                                                                   :> Get
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           MlsE2EIdConfig))))))))))))
                        :<|> (Named
                                "put-MlsE2EIdConfig@v5"
                                (From 'V5
                                 :> (Until 'V6
                                     :> (ZUser
                                         :> (Summary "Put config for mlsE2EId"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("mlsE2EId"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (Feature
                                                                                          MlsE2EIdConfig)
                                                                                     :> Put
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             MlsE2EIdConfig)))))))))))))))
                              :<|> (Named
                                      '("put", MlsE2EIdConfig)
                                      (From 'V6
                                       :> (Description ""
                                           :> (ZUser
                                               :> (Summary "Put config for mlsE2EId"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("mlsE2EId"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (Feature
                                                                                                MlsE2EIdConfig)
                                                                                           :> Put
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   MlsE2EIdConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", MlsMigrationConfig)
                                             (From 'V5
                                              :> (Description ""
                                                  :> (ZUser
                                                      :> (Summary "Get config for mlsMigration"
                                                          :> (CanThrow OperationDenied
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mlsMigration"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              MlsMigrationConfig))))))))))))
                                           :<|> Named
                                                  '("put", MlsMigrationConfig)
                                                  (From 'V5
                                                   :> (Description ""
                                                       :> (ZUser
                                                           :> (Summary "Put config for mlsMigration"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("mlsMigration"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (Feature
                                                                                                            MlsMigrationConfig)
                                                                                                       :> Put
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               MlsMigrationConfig))))))))))))))))
                                          :<|> ((Named
                                                   '("get", EnforceFileDownloadLocationConfig)
                                                   (From 'V5
                                                    :> (Description
                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                        :> (ZUser
                                                            :> (Summary
                                                                  "Get config for enforceFileDownloadLocation"
                                                                :> (CanThrow OperationDenied
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("enforceFileDownloadLocation"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    EnforceFileDownloadLocationConfig))))))))))))
                                                 :<|> Named
                                                        '("put", EnforceFileDownloadLocationConfig)
                                                        (From 'V5
                                                         :> (Description
                                                               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                             :> (ZUser
                                                                 :> (Summary
                                                                       "Put config for enforceFileDownloadLocation"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("enforceFileDownloadLocation"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (Feature
                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                             :> Put
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     EnforceFileDownloadLocationConfig))))))))))))))))
                                                :<|> (Named
                                                        '("get", LimitedEventFanoutConfig)
                                                        (From 'V5
                                                         :> (Description ""
                                                             :> (ZUser
                                                                 :> (Summary
                                                                       "Get config for limitedEventFanout"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("limitedEventFanout"
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         LimitedEventFanoutConfig))))))))))))
                                                      :<|> (Named
                                                              "get-all-feature-configs-for-user"
                                                              (Summary
                                                                 "Gets feature configs for a user"
                                                               :> (Description
                                                                     "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                   :> (DescriptionOAuthScope
                                                                         'ReadFeatureConfigs
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> Get
                                                                                                '[JSON]
                                                                                                AllTeamFeatures))))))))
                                                            :<|> (Named
                                                                    "get-all-feature-configs-for-team"
                                                                    (Summary
                                                                       "Gets feature configs for a team"
                                                                     :> (Description
                                                                           "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (ZLocalUser
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          AllTeamFeatures)))))))))
                                                                  :<|> ((Named
                                                                           '("get-deprecated",
                                                                             SearchVisibilityAvailableConfig)
                                                                           (ZUser
                                                                            :> (Summary
                                                                                  "[deprecated] Get config for searchVisibility"
                                                                                :> (Until 'V2
                                                                                    :> (Description
                                                                                          "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  OperationDenied
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("search-visibility"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            SearchVisibilityAvailableConfig))))))))))))
                                                                         :<|> (Named
                                                                                 '("put-deprecated",
                                                                                   SearchVisibilityAvailableConfig)
                                                                                 (ZUser
                                                                                  :> (Summary
                                                                                        "[deprecated] Get config for searchVisibility"
                                                                                      :> (Until 'V2
                                                                                          :> (Description
                                                                                                "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        OperationDenied
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("search-visibility"
                                                                                                                              :> (ReqBody
                                                                                                                                    '[JSON]
                                                                                                                                    (Feature
                                                                                                                                       SearchVisibilityAvailableConfig)
                                                                                                                                  :> Put
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          SearchVisibilityAvailableConfig))))))))))))))
                                                                               :<|> (Named
                                                                                       '("get-deprecated",
                                                                                         ValidateSAMLEmailsConfig)
                                                                                       (ZUser
                                                                                        :> (Summary
                                                                                              "[deprecated] Get config for validateSAMLemails"
                                                                                            :> (Until
                                                                                                  'V2
                                                                                                :> (Description
                                                                                                      "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              OperationDenied
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("validate-saml-emails"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        ValidateSAMLEmailsConfig))))))))))))
                                                                                     :<|> Named
                                                                                            '("get-deprecated",
                                                                                              DigitalSignaturesConfig)
                                                                                            (ZUser
                                                                                             :> (Summary
                                                                                                   "[deprecated] Get config for digitalSignatures"
                                                                                                 :> (Until
                                                                                                       'V2
                                                                                                     :> (Description
                                                                                                           "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("digital-signatures"
                                                                                                                                     :> Get
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             DigitalSignaturesConfig)))))))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  LegalholdConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature legalhold"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("legalhold"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         LegalholdConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        SSOConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature sso"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("sso"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               SSOConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              SearchVisibilityAvailableConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature searchVisibility"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("searchVisibility"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     SearchVisibilityAvailableConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    ValidateSAMLEmailsConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("validateSAMLemails"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           ValidateSAMLEmailsConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          DigitalSignaturesConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("digitalSignatures"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 DigitalSignaturesConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                AppLockConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature appLock"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("appLock"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       AppLockConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      FileSharingConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature fileSharing"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("fileSharing"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             FileSharingConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            ClassifiedDomainsConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("classifiedDomains"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   ClassifiedDomainsConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  ConferenceCallingConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("conferenceCalling"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         ConferenceCallingConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        SelfDeletingMessagesConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("selfDeletingMessages"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               SelfDeletingMessagesConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              GuestLinksConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     GuestLinksConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                :<|> Named
                                                                                                                                                       '("get-config",
                                                                                                                                                         MLSConfig)
                                                                                                                                                       (Summary
                                                                                                                                                          "[deprecated] Get feature config for feature mls"
                                                                                                                                                        :> (Until
                                                                                                                                                              'V2
                                                                                                                                                            :> (Description
                                                                                                                                                                  "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                :> (ZUser
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              OperationDenied
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                :> ("feature-configs"
                                                                                                                                                                                    :> ("mls"
                                                                                                                                                                                        :> Get
                                                                                                                                                                                             '[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
         '("get", MLSConfig)
         (From 'V5
          :> (Description ""
              :> (ZUser
                  :> (Summary "Get config for mls"
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("mls"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature MLSConfig))))))))))))
       :<|> Named
              '("put", MLSConfig)
              (From 'V5
               :> (Description ""
                   :> (ZUser
                       :> (Summary "Put config for mls"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("mls"
                                                               :> (ReqBody
                                                                     '[JSON] (Feature MLSConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           MLSConfig))))))))))))))))
      :<|> ((Named
               '("get", ExposeInvitationURLsToTeamAdminConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("exposeInvitationURLsToTeamAdmin"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            ExposeInvitationURLsToTeamAdminConfig)))))))))))
             :<|> Named
                    '("put", ExposeInvitationURLsToTeamAdminConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("exposeInvitationURLsToTeamAdmin"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          ExposeInvitationURLsToTeamAdminConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
            :<|> ((Named
                     '("get", SearchVisibilityInboundConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for searchVisibilityInbound"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("searchVisibilityInbound"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  SearchVisibilityInboundConfig)))))))))))
                   :<|> Named
                          '("put", SearchVisibilityInboundConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for searchVisibilityInbound"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("searchVisibilityInbound"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                SearchVisibilityInboundConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   SearchVisibilityInboundConfig)))))))))))))))
                  :<|> ((Named
                           '("get", OutlookCalIntegrationConfig)
                           (Description ""
                            :> (ZUser
                                :> (Summary "Get config for outlookCalIntegration"
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow 'TeamNotFound
                                                :> ("teams"
                                                    :> (Capture "tid" TeamId
                                                        :> ("features"
                                                            :> ("outlookCalIntegration"
                                                                :> Get
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        OutlookCalIntegrationConfig)))))))))))
                         :<|> Named
                                '("put", OutlookCalIntegrationConfig)
                                (Description ""
                                 :> (ZUser
                                     :> (Summary "Put config for outlookCalIntegration"
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow 'TeamNotFound
                                                     :> (CanThrow TeamFeatureError
                                                         :> (CanThrowMany '[]
                                                             :> ("teams"
                                                                 :> (Capture "tid" TeamId
                                                                     :> ("features"
                                                                         :> ("outlookCalIntegration"
                                                                             :> (ReqBody
                                                                                   '[JSON]
                                                                                   (Feature
                                                                                      OutlookCalIntegrationConfig)
                                                                                 :> Put
                                                                                      '[JSON]
                                                                                      (LockableFeature
                                                                                         OutlookCalIntegrationConfig)))))))))))))))
                        :<|> (Named
                                '("get", MlsE2EIdConfig)
                                (From 'V5
                                 :> (Description ""
                                     :> (ZUser
                                         :> (Summary "Get config for mlsE2EId"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("mlsE2EId"
                                                                         :> Get
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 MlsE2EIdConfig))))))))))))
                              :<|> (Named
                                      "put-MlsE2EIdConfig@v5"
                                      (From 'V5
                                       :> (Until 'V6
                                           :> (ZUser
                                               :> (Summary "Put config for mlsE2EId"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("mlsE2EId"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (Feature
                                                                                                MlsE2EIdConfig)
                                                                                           :> Put
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   MlsE2EIdConfig)))))))))))))))
                                    :<|> (Named
                                            '("put", MlsE2EIdConfig)
                                            (From 'V6
                                             :> (Description ""
                                                 :> (ZUser
                                                     :> (Summary "Put config for mlsE2EId"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("mlsE2EId"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (Feature
                                                                                                      MlsE2EIdConfig)
                                                                                                 :> Put
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         MlsE2EIdConfig)))))))))))))))
                                          :<|> ((Named
                                                   '("get", MlsMigrationConfig)
                                                   (From 'V5
                                                    :> (Description ""
                                                        :> (ZUser
                                                            :> (Summary
                                                                  "Get config for mlsMigration"
                                                                :> (CanThrow OperationDenied
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("mlsMigration"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    MlsMigrationConfig))))))))))))
                                                 :<|> Named
                                                        '("put", MlsMigrationConfig)
                                                        (From 'V5
                                                         :> (Description ""
                                                             :> (ZUser
                                                                 :> (Summary
                                                                       "Put config for mlsMigration"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("mlsMigration"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (Feature
                                                                                                                  MlsMigrationConfig)
                                                                                                             :> Put
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     MlsMigrationConfig))))))))))))))))
                                                :<|> ((Named
                                                         '("get", EnforceFileDownloadLocationConfig)
                                                         (From 'V5
                                                          :> (Description
                                                                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                              :> (ZUser
                                                                  :> (Summary
                                                                        "Get config for enforceFileDownloadLocation"
                                                                      :> (CanThrow OperationDenied
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("enforceFileDownloadLocation"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          EnforceFileDownloadLocationConfig))))))))))))
                                                       :<|> Named
                                                              '("put",
                                                                EnforceFileDownloadLocationConfig)
                                                              (From 'V5
                                                               :> (Description
                                                                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Put config for enforceFileDownloadLocation"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> (CanThrow
                                                                                             TeamFeatureError
                                                                                           :> (CanThrowMany
                                                                                                 '[]
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> ("enforceFileDownloadLocation"
                                                                                                               :> (ReqBody
                                                                                                                     '[JSON]
                                                                                                                     (Feature
                                                                                                                        EnforceFileDownloadLocationConfig)
                                                                                                                   :> Put
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           EnforceFileDownloadLocationConfig))))))))))))))))
                                                      :<|> (Named
                                                              '("get", LimitedEventFanoutConfig)
                                                              (From 'V5
                                                               :> (Description ""
                                                                   :> (ZUser
                                                                       :> (Summary
                                                                             "Get config for limitedEventFanout"
                                                                           :> (CanThrow
                                                                                 OperationDenied
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("limitedEventFanout"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               LimitedEventFanoutConfig))))))))))))
                                                            :<|> (Named
                                                                    "get-all-feature-configs-for-user"
                                                                    (Summary
                                                                       "Gets feature configs for a user"
                                                                     :> (Description
                                                                           "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                         :> (DescriptionOAuthScope
                                                                               'ReadFeatureConfigs
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      AllTeamFeatures))))))))
                                                                  :<|> (Named
                                                                          "get-all-feature-configs-for-team"
                                                                          (Summary
                                                                             "Gets feature configs for a team"
                                                                           :> (Description
                                                                                 "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                               :> (CanThrow
                                                                                     'NotATeamMember
                                                                                   :> (CanThrow
                                                                                         OperationDenied
                                                                                       :> (CanThrow
                                                                                             'TeamNotFound
                                                                                           :> (ZLocalUser
                                                                                               :> ("teams"
                                                                                                   :> (Capture
                                                                                                         "tid"
                                                                                                         TeamId
                                                                                                       :> ("features"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                AllTeamFeatures)))))))))
                                                                        :<|> ((Named
                                                                                 '("get-deprecated",
                                                                                   SearchVisibilityAvailableConfig)
                                                                                 (ZUser
                                                                                  :> (Summary
                                                                                        "[deprecated] Get config for searchVisibility"
                                                                                      :> (Until 'V2
                                                                                          :> (Description
                                                                                                "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        OperationDenied
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("search-visibility"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  SearchVisibilityAvailableConfig))))))))))))
                                                                               :<|> (Named
                                                                                       '("put-deprecated",
                                                                                         SearchVisibilityAvailableConfig)
                                                                                       (ZUser
                                                                                        :> (Summary
                                                                                              "[deprecated] Get config for searchVisibility"
                                                                                            :> (Until
                                                                                                  'V2
                                                                                                :> (Description
                                                                                                      "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              OperationDenied
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> (CanThrow
                                                                                                                      TeamFeatureError
                                                                                                                    :> ("teams"
                                                                                                                        :> (Capture
                                                                                                                              "tid"
                                                                                                                              TeamId
                                                                                                                            :> ("features"
                                                                                                                                :> ("search-visibility"
                                                                                                                                    :> (ReqBody
                                                                                                                                          '[JSON]
                                                                                                                                          (Feature
                                                                                                                                             SearchVisibilityAvailableConfig)
                                                                                                                                        :> Put
                                                                                                                                             '[JSON]
                                                                                                                                             (LockableFeature
                                                                                                                                                SearchVisibilityAvailableConfig))))))))))))))
                                                                                     :<|> (Named
                                                                                             '("get-deprecated",
                                                                                               ValidateSAMLEmailsConfig)
                                                                                             (ZUser
                                                                                              :> (Summary
                                                                                                    "[deprecated] Get config for validateSAMLemails"
                                                                                                  :> (Until
                                                                                                        'V2
                                                                                                      :> (Description
                                                                                                            "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                          :> (CanThrow
                                                                                                                'NotATeamMember
                                                                                                              :> (CanThrow
                                                                                                                    OperationDenied
                                                                                                                  :> (CanThrow
                                                                                                                        'TeamNotFound
                                                                                                                      :> ("teams"
                                                                                                                          :> (Capture
                                                                                                                                "tid"
                                                                                                                                TeamId
                                                                                                                              :> ("features"
                                                                                                                                  :> ("validate-saml-emails"
                                                                                                                                      :> Get
                                                                                                                                           '[JSON]
                                                                                                                                           (LockableFeature
                                                                                                                                              ValidateSAMLEmailsConfig))))))))))))
                                                                                           :<|> Named
                                                                                                  '("get-deprecated",
                                                                                                    DigitalSignaturesConfig)
                                                                                                  (ZUser
                                                                                                   :> (Summary
                                                                                                         "[deprecated] Get config for digitalSignatures"
                                                                                                       :> (Until
                                                                                                             'V2
                                                                                                           :> (Description
                                                                                                                 "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("teams"
                                                                                                                               :> (Capture
                                                                                                                                     "tid"
                                                                                                                                     TeamId
                                                                                                                                   :> ("features"
                                                                                                                                       :> ("digital-signatures"
                                                                                                                                           :> Get
                                                                                                                                                '[JSON]
                                                                                                                                                (LockableFeature
                                                                                                                                                   DigitalSignaturesConfig)))))))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        LegalholdConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature legalhold"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("legalhold"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               LegalholdConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              SSOConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature sso"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("sso"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     SSOConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    SearchVisibilityAvailableConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature searchVisibility"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("searchVisibility"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           SearchVisibilityAvailableConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          ValidateSAMLEmailsConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("validateSAMLemails"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 ValidateSAMLEmailsConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                DigitalSignaturesConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("digitalSignatures"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       DigitalSignaturesConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      AppLockConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature appLock"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("appLock"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             AppLockConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            FileSharingConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature fileSharing"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("fileSharing"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   FileSharingConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  ClassifiedDomainsConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("classifiedDomains"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         ClassifiedDomainsConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        ConferenceCallingConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("conferenceCalling"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               ConferenceCallingConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              SelfDeletingMessagesConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("selfDeletingMessages"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     SelfDeletingMessagesConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    GuestLinksConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           GuestLinksConfig))))))))))
                                                                                                                                                :<|> (Named
                                                                                                                                                        '("get-config",
                                                                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                                                                        (Summary
                                                                                                                                                           "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                         :> (Until
                                                                                                                                                               'V2
                                                                                                                                                             :> (Description
                                                                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                 :> (ZUser
                                                                                                                                                                     :> (CanThrow
                                                                                                                                                                           'NotATeamMember
                                                                                                                                                                         :> (CanThrow
                                                                                                                                                                               OperationDenied
                                                                                                                                                                             :> (CanThrow
                                                                                                                                                                                   'TeamNotFound
                                                                                                                                                                                 :> ("feature-configs"
                                                                                                                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                         :> Get
                                                                                                                                                                                              '[JSON]
                                                                                                                                                                                              (LockableFeature
                                                                                                                                                                                                 SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                      :<|> Named
                                                                                                                                                             '("get-config",
                                                                                                                                                               MLSConfig)
                                                                                                                                                             (Summary
                                                                                                                                                                "[deprecated] Get feature config for feature mls"
                                                                                                                                                              :> (Until
                                                                                                                                                                    'V2
                                                                                                                                                                  :> (Description
                                                                                                                                                                        "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                      :> (ZUser
                                                                                                                                                                          :> (CanThrow
                                                                                                                                                                                'NotATeamMember
                                                                                                                                                                              :> (CanThrow
                                                                                                                                                                                    OperationDenied
                                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                                        'TeamNotFound
                                                                                                                                                                                      :> ("feature-configs"
                                                                                                                                                                                          :> ("mls"
                                                                                                                                                                                              :> Get
                                                                                                                                                                                                   '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     '("get", ExposeInvitationURLsToTeamAdminConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("exposeInvitationURLsToTeamAdmin"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  ExposeInvitationURLsToTeamAdminConfig)))))))))))
   :<|> Named
          '("put", ExposeInvitationURLsToTeamAdminConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("exposeInvitationURLsToTeamAdmin"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature
                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                           :> Put
                                                                '[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
     '("get", ExposeInvitationURLsToTeamAdminConfig)
     (Description (FeatureAPIDesc ExposeInvitationURLsToTeamAdminConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol
                   "Get config for "
                   (FeatureSymbol ExposeInvitationURLsToTeamAdminConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol ExposeInvitationURLsToTeamAdminConfig
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  ExposeInvitationURLsToTeamAdminConfig)))))))))))
   :<|> Named
          '("put", ExposeInvitationURLsToTeamAdminConfig)
          (Description (FeatureAPIDesc ExposeInvitationURLsToTeamAdminConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol
                        "Put config for "
                        (FeatureSymbol ExposeInvitationURLsToTeamAdminConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany
                                         (FeatureErrors ExposeInvitationURLsToTeamAdminConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol
                                                         ExposeInvitationURLsToTeamAdminConfig
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature
                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", ExposeInvitationURLsToTeamAdminConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("exposeInvitationURLsToTeamAdmin"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  ExposeInvitationURLsToTeamAdminConfig)))))))))))
   :<|> Named
          '("put", ExposeInvitationURLsToTeamAdminConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("exposeInvitationURLsToTeamAdmin"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature
                                                                ExposeInvitationURLsToTeamAdminConfig)
                                                           :> Put
                                                                '[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
         '("get", SearchVisibilityInboundConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for searchVisibilityInbound"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("searchVisibilityInbound"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      SearchVisibilityInboundConfig)))))))))))
       :<|> Named
              '("put", SearchVisibilityInboundConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for searchVisibilityInbound"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("searchVisibilityInbound"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    SearchVisibilityInboundConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       SearchVisibilityInboundConfig)))))))))))))))
      :<|> ((Named
               '("get", OutlookCalIntegrationConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for outlookCalIntegration"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("outlookCalIntegration"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            OutlookCalIntegrationConfig)))))))))))
             :<|> Named
                    '("put", OutlookCalIntegrationConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for outlookCalIntegration"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("outlookCalIntegration"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          OutlookCalIntegrationConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             OutlookCalIntegrationConfig)))))))))))))))
            :<|> (Named
                    '("get", MlsE2EIdConfig)
                    (From 'V5
                     :> (Description ""
                         :> (ZUser
                             :> (Summary "Get config for mlsE2EId"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mlsE2EId"
                                                             :> Get
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MlsE2EIdConfig))))))))))))
                  :<|> (Named
                          "put-MlsE2EIdConfig@v5"
                          (From 'V5
                           :> (Until 'V6
                               :> (ZUser
                                   :> (Summary "Put config for mlsE2EId"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("mlsE2EId"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (Feature
                                                                                    MlsE2EIdConfig)
                                                                               :> Put
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       MlsE2EIdConfig)))))))))))))))
                        :<|> (Named
                                '("put", MlsE2EIdConfig)
                                (From 'V6
                                 :> (Description ""
                                     :> (ZUser
                                         :> (Summary "Put config for mlsE2EId"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("mlsE2EId"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (Feature
                                                                                          MlsE2EIdConfig)
                                                                                     :> Put
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             MlsE2EIdConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", MlsMigrationConfig)
                                       (From 'V5
                                        :> (Description ""
                                            :> (ZUser
                                                :> (Summary "Get config for mlsMigration"
                                                    :> (CanThrow OperationDenied
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("mlsMigration"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        MlsMigrationConfig))))))))))))
                                     :<|> Named
                                            '("put", MlsMigrationConfig)
                                            (From 'V5
                                             :> (Description ""
                                                 :> (ZUser
                                                     :> (Summary "Put config for mlsMigration"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("mlsMigration"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (Feature
                                                                                                      MlsMigrationConfig)
                                                                                                 :> Put
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         MlsMigrationConfig))))))))))))))))
                                    :<|> ((Named
                                             '("get", EnforceFileDownloadLocationConfig)
                                             (From 'V5
                                              :> (Description
                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                  :> (ZUser
                                                      :> (Summary
                                                            "Get config for enforceFileDownloadLocation"
                                                          :> (CanThrow OperationDenied
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("enforceFileDownloadLocation"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              EnforceFileDownloadLocationConfig))))))))))))
                                           :<|> Named
                                                  '("put", EnforceFileDownloadLocationConfig)
                                                  (From 'V5
                                                   :> (Description
                                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                       :> (ZUser
                                                           :> (Summary
                                                                 "Put config for enforceFileDownloadLocation"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("enforceFileDownloadLocation"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (Feature
                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                       :> Put
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               EnforceFileDownloadLocationConfig))))))))))))))))
                                          :<|> (Named
                                                  '("get", LimitedEventFanoutConfig)
                                                  (From 'V5
                                                   :> (Description ""
                                                       :> (ZUser
                                                           :> (Summary
                                                                 "Get config for limitedEventFanout"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("limitedEventFanout"
                                                                                           :> Get
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   LimitedEventFanoutConfig))))))))))))
                                                :<|> (Named
                                                        "get-all-feature-configs-for-user"
                                                        (Summary "Gets feature configs for a user"
                                                         :> (Description
                                                               "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                             :> (DescriptionOAuthScope
                                                                   'ReadFeatureConfigs
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> Get
                                                                                          '[JSON]
                                                                                          AllTeamFeatures))))))))
                                                      :<|> (Named
                                                              "get-all-feature-configs-for-team"
                                                              (Summary
                                                                 "Gets feature configs for a team"
                                                               :> (Description
                                                                     "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (ZLocalUser
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    AllTeamFeatures)))))))))
                                                            :<|> ((Named
                                                                     '("get-deprecated",
                                                                       SearchVisibilityAvailableConfig)
                                                                     (ZUser
                                                                      :> (Summary
                                                                            "[deprecated] Get config for searchVisibility"
                                                                          :> (Until 'V2
                                                                              :> (Description
                                                                                    "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            OperationDenied
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("search-visibility"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      SearchVisibilityAvailableConfig))))))))))))
                                                                   :<|> (Named
                                                                           '("put-deprecated",
                                                                             SearchVisibilityAvailableConfig)
                                                                           (ZUser
                                                                            :> (Summary
                                                                                  "[deprecated] Get config for searchVisibility"
                                                                                :> (Until 'V2
                                                                                    :> (Description
                                                                                          "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  OperationDenied
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("search-visibility"
                                                                                                                        :> (ReqBody
                                                                                                                              '[JSON]
                                                                                                                              (Feature
                                                                                                                                 SearchVisibilityAvailableConfig)
                                                                                                                            :> Put
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    SearchVisibilityAvailableConfig))))))))))))))
                                                                         :<|> (Named
                                                                                 '("get-deprecated",
                                                                                   ValidateSAMLEmailsConfig)
                                                                                 (ZUser
                                                                                  :> (Summary
                                                                                        "[deprecated] Get config for validateSAMLemails"
                                                                                      :> (Until 'V2
                                                                                          :> (Description
                                                                                                "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        OperationDenied
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("validate-saml-emails"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  ValidateSAMLEmailsConfig))))))))))))
                                                                               :<|> Named
                                                                                      '("get-deprecated",
                                                                                        DigitalSignaturesConfig)
                                                                                      (ZUser
                                                                                       :> (Summary
                                                                                             "[deprecated] Get config for digitalSignatures"
                                                                                           :> (Until
                                                                                                 'V2
                                                                                               :> (Description
                                                                                                     "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("digital-signatures"
                                                                                                                               :> Get
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       DigitalSignaturesConfig)))))))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            LegalholdConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature legalhold"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("legalhold"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   LegalholdConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  SSOConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature sso"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("sso"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         SSOConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        SearchVisibilityAvailableConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature searchVisibility"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("searchVisibility"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               SearchVisibilityAvailableConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              ValidateSAMLEmailsConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("validateSAMLemails"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     ValidateSAMLEmailsConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    DigitalSignaturesConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("digitalSignatures"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           DigitalSignaturesConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          AppLockConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature appLock"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("appLock"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 AppLockConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                FileSharingConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature fileSharing"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("fileSharing"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       FileSharingConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      ClassifiedDomainsConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("classifiedDomains"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             ClassifiedDomainsConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            ConferenceCallingConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("conferenceCalling"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   ConferenceCallingConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  SelfDeletingMessagesConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("selfDeletingMessages"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         SelfDeletingMessagesConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        GuestLinksConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               GuestLinksConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              SndFactorPasswordChallengeConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                          :<|> Named
                                                                                                                                                 '("get-config",
                                                                                                                                                   MLSConfig)
                                                                                                                                                 (Summary
                                                                                                                                                    "[deprecated] Get feature config for feature mls"
                                                                                                                                                  :> (Until
                                                                                                                                                        'V2
                                                                                                                                                      :> (Description
                                                                                                                                                            "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                          :> (ZUser
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        OperationDenied
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                          :> ("feature-configs"
                                                                                                                                                                              :> ("mls"
                                                                                                                                                                                  :> Get
                                                                                                                                                                                       '[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
         '("get", ExposeInvitationURLsToTeamAdminConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for exposeInvitationURLsToTeamAdmin"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("exposeInvitationURLsToTeamAdmin"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      ExposeInvitationURLsToTeamAdminConfig)))))))))))
       :<|> Named
              '("put", ExposeInvitationURLsToTeamAdminConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for exposeInvitationURLsToTeamAdmin"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("exposeInvitationURLsToTeamAdmin"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    ExposeInvitationURLsToTeamAdminConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       ExposeInvitationURLsToTeamAdminConfig)))))))))))))))
      :<|> ((Named
               '("get", SearchVisibilityInboundConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for searchVisibilityInbound"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("searchVisibilityInbound"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            SearchVisibilityInboundConfig)))))))))))
             :<|> Named
                    '("put", SearchVisibilityInboundConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for searchVisibilityInbound"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("searchVisibilityInbound"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          SearchVisibilityInboundConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             SearchVisibilityInboundConfig)))))))))))))))
            :<|> ((Named
                     '("get", OutlookCalIntegrationConfig)
                     (Description ""
                      :> (ZUser
                          :> (Summary "Get config for outlookCalIntegration"
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("outlookCalIntegration"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  OutlookCalIntegrationConfig)))))))))))
                   :<|> Named
                          '("put", OutlookCalIntegrationConfig)
                          (Description ""
                           :> (ZUser
                               :> (Summary "Put config for outlookCalIntegration"
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow 'TeamNotFound
                                               :> (CanThrow TeamFeatureError
                                                   :> (CanThrowMany '[]
                                                       :> ("teams"
                                                           :> (Capture "tid" TeamId
                                                               :> ("features"
                                                                   :> ("outlookCalIntegration"
                                                                       :> (ReqBody
                                                                             '[JSON]
                                                                             (Feature
                                                                                OutlookCalIntegrationConfig)
                                                                           :> Put
                                                                                '[JSON]
                                                                                (LockableFeature
                                                                                   OutlookCalIntegrationConfig)))))))))))))))
                  :<|> (Named
                          '("get", MlsE2EIdConfig)
                          (From 'V5
                           :> (Description ""
                               :> (ZUser
                                   :> (Summary "Get config for mlsE2EId"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("mlsE2EId"
                                                                   :> Get
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           MlsE2EIdConfig))))))))))))
                        :<|> (Named
                                "put-MlsE2EIdConfig@v5"
                                (From 'V5
                                 :> (Until 'V6
                                     :> (ZUser
                                         :> (Summary "Put config for mlsE2EId"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("mlsE2EId"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (Feature
                                                                                          MlsE2EIdConfig)
                                                                                     :> Put
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             MlsE2EIdConfig)))))))))))))))
                              :<|> (Named
                                      '("put", MlsE2EIdConfig)
                                      (From 'V6
                                       :> (Description ""
                                           :> (ZUser
                                               :> (Summary "Put config for mlsE2EId"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("mlsE2EId"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (Feature
                                                                                                MlsE2EIdConfig)
                                                                                           :> Put
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   MlsE2EIdConfig)))))))))))))))
                                    :<|> ((Named
                                             '("get", MlsMigrationConfig)
                                             (From 'V5
                                              :> (Description ""
                                                  :> (ZUser
                                                      :> (Summary "Get config for mlsMigration"
                                                          :> (CanThrow OperationDenied
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("mlsMigration"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              MlsMigrationConfig))))))))))))
                                           :<|> Named
                                                  '("put", MlsMigrationConfig)
                                                  (From 'V5
                                                   :> (Description ""
                                                       :> (ZUser
                                                           :> (Summary "Put config for mlsMigration"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("mlsMigration"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (Feature
                                                                                                            MlsMigrationConfig)
                                                                                                       :> Put
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               MlsMigrationConfig))))))))))))))))
                                          :<|> ((Named
                                                   '("get", EnforceFileDownloadLocationConfig)
                                                   (From 'V5
                                                    :> (Description
                                                          "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                        :> (ZUser
                                                            :> (Summary
                                                                  "Get config for enforceFileDownloadLocation"
                                                                :> (CanThrow OperationDenied
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("enforceFileDownloadLocation"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    EnforceFileDownloadLocationConfig))))))))))))
                                                 :<|> Named
                                                        '("put", EnforceFileDownloadLocationConfig)
                                                        (From 'V5
                                                         :> (Description
                                                               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                             :> (ZUser
                                                                 :> (Summary
                                                                       "Put config for enforceFileDownloadLocation"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> (CanThrow
                                                                                       TeamFeatureError
                                                                                     :> (CanThrowMany
                                                                                           '[]
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> ("enforceFileDownloadLocation"
                                                                                                         :> (ReqBody
                                                                                                               '[JSON]
                                                                                                               (Feature
                                                                                                                  EnforceFileDownloadLocationConfig)
                                                                                                             :> Put
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     EnforceFileDownloadLocationConfig))))))))))))))))
                                                :<|> (Named
                                                        '("get", LimitedEventFanoutConfig)
                                                        (From 'V5
                                                         :> (Description ""
                                                             :> (ZUser
                                                                 :> (Summary
                                                                       "Get config for limitedEventFanout"
                                                                     :> (CanThrow OperationDenied
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("limitedEventFanout"
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         LimitedEventFanoutConfig))))))))))))
                                                      :<|> (Named
                                                              "get-all-feature-configs-for-user"
                                                              (Summary
                                                                 "Gets feature configs for a user"
                                                               :> (Description
                                                                     "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                                   :> (DescriptionOAuthScope
                                                                         'ReadFeatureConfigs
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> Get
                                                                                                '[JSON]
                                                                                                AllTeamFeatures))))))))
                                                            :<|> (Named
                                                                    "get-all-feature-configs-for-team"
                                                                    (Summary
                                                                       "Gets feature configs for a team"
                                                                     :> (Description
                                                                           "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                         :> (CanThrow
                                                                               'NotATeamMember
                                                                             :> (CanThrow
                                                                                   OperationDenied
                                                                                 :> (CanThrow
                                                                                       'TeamNotFound
                                                                                     :> (ZLocalUser
                                                                                         :> ("teams"
                                                                                             :> (Capture
                                                                                                   "tid"
                                                                                                   TeamId
                                                                                                 :> ("features"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          AllTeamFeatures)))))))))
                                                                  :<|> ((Named
                                                                           '("get-deprecated",
                                                                             SearchVisibilityAvailableConfig)
                                                                           (ZUser
                                                                            :> (Summary
                                                                                  "[deprecated] Get config for searchVisibility"
                                                                                :> (Until 'V2
                                                                                    :> (Description
                                                                                          "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  OperationDenied
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("search-visibility"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            SearchVisibilityAvailableConfig))))))))))))
                                                                         :<|> (Named
                                                                                 '("put-deprecated",
                                                                                   SearchVisibilityAvailableConfig)
                                                                                 (ZUser
                                                                                  :> (Summary
                                                                                        "[deprecated] Get config for searchVisibility"
                                                                                      :> (Until 'V2
                                                                                          :> (Description
                                                                                                "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        OperationDenied
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> (CanThrow
                                                                                                                TeamFeatureError
                                                                                                              :> ("teams"
                                                                                                                  :> (Capture
                                                                                                                        "tid"
                                                                                                                        TeamId
                                                                                                                      :> ("features"
                                                                                                                          :> ("search-visibility"
                                                                                                                              :> (ReqBody
                                                                                                                                    '[JSON]
                                                                                                                                    (Feature
                                                                                                                                       SearchVisibilityAvailableConfig)
                                                                                                                                  :> Put
                                                                                                                                       '[JSON]
                                                                                                                                       (LockableFeature
                                                                                                                                          SearchVisibilityAvailableConfig))))))))))))))
                                                                               :<|> (Named
                                                                                       '("get-deprecated",
                                                                                         ValidateSAMLEmailsConfig)
                                                                                       (ZUser
                                                                                        :> (Summary
                                                                                              "[deprecated] Get config for validateSAMLemails"
                                                                                            :> (Until
                                                                                                  'V2
                                                                                                :> (Description
                                                                                                      "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                                    :> (CanThrow
                                                                                                          'NotATeamMember
                                                                                                        :> (CanThrow
                                                                                                              OperationDenied
                                                                                                            :> (CanThrow
                                                                                                                  'TeamNotFound
                                                                                                                :> ("teams"
                                                                                                                    :> (Capture
                                                                                                                          "tid"
                                                                                                                          TeamId
                                                                                                                        :> ("features"
                                                                                                                            :> ("validate-saml-emails"
                                                                                                                                :> Get
                                                                                                                                     '[JSON]
                                                                                                                                     (LockableFeature
                                                                                                                                        ValidateSAMLEmailsConfig))))))))))))
                                                                                     :<|> Named
                                                                                            '("get-deprecated",
                                                                                              DigitalSignaturesConfig)
                                                                                            (ZUser
                                                                                             :> (Summary
                                                                                                   "[deprecated] Get config for digitalSignatures"
                                                                                                 :> (Until
                                                                                                       'V2
                                                                                                     :> (Description
                                                                                                           "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("teams"
                                                                                                                         :> (Capture
                                                                                                                               "tid"
                                                                                                                               TeamId
                                                                                                                             :> ("features"
                                                                                                                                 :> ("digital-signatures"
                                                                                                                                     :> Get
                                                                                                                                          '[JSON]
                                                                                                                                          (LockableFeature
                                                                                                                                             DigitalSignaturesConfig)))))))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  LegalholdConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature legalhold"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("legalhold"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         LegalholdConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        SSOConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature sso"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("sso"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               SSOConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              SearchVisibilityAvailableConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature searchVisibility"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("searchVisibility"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     SearchVisibilityAvailableConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    ValidateSAMLEmailsConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("validateSAMLemails"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           ValidateSAMLEmailsConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          DigitalSignaturesConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("digitalSignatures"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 DigitalSignaturesConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                AppLockConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature appLock"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("appLock"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       AppLockConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      FileSharingConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature fileSharing"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("fileSharing"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             FileSharingConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            ClassifiedDomainsConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("classifiedDomains"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   ClassifiedDomainsConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  ConferenceCallingConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("conferenceCalling"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         ConferenceCallingConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        SelfDeletingMessagesConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("selfDeletingMessages"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               SelfDeletingMessagesConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              GuestLinksConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     GuestLinksConfig))))))))))
                                                                                                                                          :<|> (Named
                                                                                                                                                  '("get-config",
                                                                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                                                                                  (Summary
                                                                                                                                                     "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                                   :> (Until
                                                                                                                                                         'V2
                                                                                                                                                       :> (Description
                                                                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                           :> (ZUser
                                                                                                                                                               :> (CanThrow
                                                                                                                                                                     'NotATeamMember
                                                                                                                                                                   :> (CanThrow
                                                                                                                                                                         OperationDenied
                                                                                                                                                                       :> (CanThrow
                                                                                                                                                                             'TeamNotFound
                                                                                                                                                                           :> ("feature-configs"
                                                                                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                                                                                   :> Get
                                                                                                                                                                                        '[JSON]
                                                                                                                                                                                        (LockableFeature
                                                                                                                                                                                           SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                                :<|> Named
                                                                                                                                                       '("get-config",
                                                                                                                                                         MLSConfig)
                                                                                                                                                       (Summary
                                                                                                                                                          "[deprecated] Get feature config for feature mls"
                                                                                                                                                        :> (Until
                                                                                                                                                              'V2
                                                                                                                                                            :> (Description
                                                                                                                                                                  "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                                :> (ZUser
                                                                                                                                                                    :> (CanThrow
                                                                                                                                                                          'NotATeamMember
                                                                                                                                                                        :> (CanThrow
                                                                                                                                                                              OperationDenied
                                                                                                                                                                            :> (CanThrow
                                                                                                                                                                                  'TeamNotFound
                                                                                                                                                                                :> ("feature-configs"
                                                                                                                                                                                    :> ("mls"
                                                                                                                                                                                        :> Get
                                                                                                                                                                                             '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     '("get", SearchVisibilityInboundConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for searchVisibilityInbound"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("searchVisibilityInbound"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SearchVisibilityInboundConfig)))))))))))
   :<|> Named
          '("put", SearchVisibilityInboundConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for searchVisibilityInbound"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("searchVisibilityInbound"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature SearchVisibilityInboundConfig)
                                                           :> Put
                                                                '[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
     '("get", SearchVisibilityInboundConfig)
     (Description (FeatureAPIDesc SearchVisibilityInboundConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol
                   "Get config for " (FeatureSymbol SearchVisibilityInboundConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol SearchVisibilityInboundConfig
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SearchVisibilityInboundConfig)))))))))))
   :<|> Named
          '("put", SearchVisibilityInboundConfig)
          (Description (FeatureAPIDesc SearchVisibilityInboundConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol
                        "Put config for " (FeatureSymbol SearchVisibilityInboundConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors SearchVisibilityInboundConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol SearchVisibilityInboundConfig
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature SearchVisibilityInboundConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", SearchVisibilityInboundConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for searchVisibilityInbound"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("searchVisibilityInbound"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  SearchVisibilityInboundConfig)))))))))))
   :<|> Named
          '("put", SearchVisibilityInboundConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for searchVisibilityInbound"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("searchVisibilityInbound"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature SearchVisibilityInboundConfig)
                                                           :> Put
                                                                '[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
         '("get", OutlookCalIntegrationConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for outlookCalIntegration"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("outlookCalIntegration"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      OutlookCalIntegrationConfig)))))))))))
       :<|> Named
              '("put", OutlookCalIntegrationConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for outlookCalIntegration"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("outlookCalIntegration"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    OutlookCalIntegrationConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       OutlookCalIntegrationConfig)))))))))))))))
      :<|> (Named
              '("get", MlsE2EIdConfig)
              (From 'V5
               :> (Description ""
                   :> (ZUser
                       :> (Summary "Get config for mlsE2EId"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("mlsE2EId"
                                                       :> Get
                                                            '[JSON]
                                                            (LockableFeature
                                                               MlsE2EIdConfig))))))))))))
            :<|> (Named
                    "put-MlsE2EIdConfig@v5"
                    (From 'V5
                     :> (Until 'V6
                         :> (ZUser
                             :> (Summary "Put config for mlsE2EId"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany '[]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("mlsE2EId"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (Feature MlsE2EIdConfig)
                                                                         :> Put
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 MlsE2EIdConfig)))))))))))))))
                  :<|> (Named
                          '("put", MlsE2EIdConfig)
                          (From 'V6
                           :> (Description ""
                               :> (ZUser
                                   :> (Summary "Put config for mlsE2EId"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("mlsE2EId"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (Feature
                                                                                    MlsE2EIdConfig)
                                                                               :> Put
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       MlsE2EIdConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", MlsMigrationConfig)
                                 (From 'V5
                                  :> (Description ""
                                      :> (ZUser
                                          :> (Summary "Get config for mlsMigration"
                                              :> (CanThrow OperationDenied
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("mlsMigration"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  MlsMigrationConfig))))))))))))
                               :<|> Named
                                      '("put", MlsMigrationConfig)
                                      (From 'V5
                                       :> (Description ""
                                           :> (ZUser
                                               :> (Summary "Put config for mlsMigration"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("mlsMigration"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (Feature
                                                                                                MlsMigrationConfig)
                                                                                           :> Put
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   MlsMigrationConfig))))))))))))))))
                              :<|> ((Named
                                       '("get", EnforceFileDownloadLocationConfig)
                                       (From 'V5
                                        :> (Description
                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                            :> (ZUser
                                                :> (Summary
                                                      "Get config for enforceFileDownloadLocation"
                                                    :> (CanThrow OperationDenied
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("enforceFileDownloadLocation"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        EnforceFileDownloadLocationConfig))))))))))))
                                     :<|> Named
                                            '("put", EnforceFileDownloadLocationConfig)
                                            (From 'V5
                                             :> (Description
                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                 :> (ZUser
                                                     :> (Summary
                                                           "Put config for enforceFileDownloadLocation"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("enforceFileDownloadLocation"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (Feature
                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                 :> Put
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         EnforceFileDownloadLocationConfig))))))))))))))))
                                    :<|> (Named
                                            '("get", LimitedEventFanoutConfig)
                                            (From 'V5
                                             :> (Description ""
                                                 :> (ZUser
                                                     :> (Summary "Get config for limitedEventFanout"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("limitedEventFanout"
                                                                                     :> Get
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             LimitedEventFanoutConfig))))))))))))
                                          :<|> (Named
                                                  "get-all-feature-configs-for-user"
                                                  (Summary "Gets feature configs for a user"
                                                   :> (Description
                                                         "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                       :> (DescriptionOAuthScope 'ReadFeatureConfigs
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> Get
                                                                                    '[JSON]
                                                                                    AllTeamFeatures))))))))
                                                :<|> (Named
                                                        "get-all-feature-configs-for-team"
                                                        (Summary "Gets feature configs for a team"
                                                         :> (Description
                                                               "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (ZLocalUser
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              AllTeamFeatures)))))))))
                                                      :<|> ((Named
                                                               '("get-deprecated",
                                                                 SearchVisibilityAvailableConfig)
                                                               (ZUser
                                                                :> (Summary
                                                                      "[deprecated] Get config for searchVisibility"
                                                                    :> (Until 'V2
                                                                        :> (Description
                                                                              "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      OperationDenied
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("search-visibility"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SearchVisibilityAvailableConfig))))))))))))
                                                             :<|> (Named
                                                                     '("put-deprecated",
                                                                       SearchVisibilityAvailableConfig)
                                                                     (ZUser
                                                                      :> (Summary
                                                                            "[deprecated] Get config for searchVisibility"
                                                                          :> (Until 'V2
                                                                              :> (Description
                                                                                    "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            OperationDenied
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("search-visibility"
                                                                                                                  :> (ReqBody
                                                                                                                        '[JSON]
                                                                                                                        (Feature
                                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                                      :> Put
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              SearchVisibilityAvailableConfig))))))))))))))
                                                                   :<|> (Named
                                                                           '("get-deprecated",
                                                                             ValidateSAMLEmailsConfig)
                                                                           (ZUser
                                                                            :> (Summary
                                                                                  "[deprecated] Get config for validateSAMLemails"
                                                                                :> (Until 'V2
                                                                                    :> (Description
                                                                                          "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  OperationDenied
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("validate-saml-emails"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            ValidateSAMLEmailsConfig))))))))))))
                                                                         :<|> Named
                                                                                '("get-deprecated",
                                                                                  DigitalSignaturesConfig)
                                                                                (ZUser
                                                                                 :> (Summary
                                                                                       "[deprecated] Get config for digitalSignatures"
                                                                                     :> (Until 'V2
                                                                                         :> (Description
                                                                                               "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("digital-signatures"
                                                                                                                         :> Get
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 DigitalSignaturesConfig)))))))))))))))
                                                            :<|> (Named
                                                                    '("get-config", LegalholdConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature legalhold"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("legalhold"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             LegalholdConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config", SSOConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature sso"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("sso"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   SSOConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  SearchVisibilityAvailableConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature searchVisibility"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("searchVisibility"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         SearchVisibilityAvailableConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        ValidateSAMLEmailsConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("validateSAMLemails"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               ValidateSAMLEmailsConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              DigitalSignaturesConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature digitalSignatures"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("digitalSignatures"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     DigitalSignaturesConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    AppLockConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature appLock"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("appLock"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           AppLockConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          FileSharingConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature fileSharing"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("fileSharing"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 FileSharingConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                ClassifiedDomainsConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("classifiedDomains"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       ClassifiedDomainsConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      ConferenceCallingConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("conferenceCalling"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             ConferenceCallingConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            SelfDeletingMessagesConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("selfDeletingMessages"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   SelfDeletingMessagesConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  GuestLinksConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         GuestLinksConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                    :<|> Named
                                                                                                                                           '("get-config",
                                                                                                                                             MLSConfig)
                                                                                                                                           (Summary
                                                                                                                                              "[deprecated] Get feature config for feature mls"
                                                                                                                                            :> (Until
                                                                                                                                                  'V2
                                                                                                                                                :> (Description
                                                                                                                                                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                    :> (ZUser
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  OperationDenied
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                    :> ("feature-configs"
                                                                                                                                                                        :> ("mls"
                                                                                                                                                                            :> Get
                                                                                                                                                                                 '[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
         '("get", SearchVisibilityInboundConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for searchVisibilityInbound"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("searchVisibilityInbound"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      SearchVisibilityInboundConfig)))))))))))
       :<|> Named
              '("put", SearchVisibilityInboundConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for searchVisibilityInbound"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("searchVisibilityInbound"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    SearchVisibilityInboundConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       SearchVisibilityInboundConfig)))))))))))))))
      :<|> ((Named
               '("get", OutlookCalIntegrationConfig)
               (Description ""
                :> (ZUser
                    :> (Summary "Get config for outlookCalIntegration"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("outlookCalIntegration"
                                                    :> Get
                                                         '[JSON]
                                                         (LockableFeature
                                                            OutlookCalIntegrationConfig)))))))))))
             :<|> Named
                    '("put", OutlookCalIntegrationConfig)
                    (Description ""
                     :> (ZUser
                         :> (Summary "Put config for outlookCalIntegration"
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow 'TeamNotFound
                                         :> (CanThrow TeamFeatureError
                                             :> (CanThrowMany '[]
                                                 :> ("teams"
                                                     :> (Capture "tid" TeamId
                                                         :> ("features"
                                                             :> ("outlookCalIntegration"
                                                                 :> (ReqBody
                                                                       '[JSON]
                                                                       (Feature
                                                                          OutlookCalIntegrationConfig)
                                                                     :> Put
                                                                          '[JSON]
                                                                          (LockableFeature
                                                                             OutlookCalIntegrationConfig)))))))))))))))
            :<|> (Named
                    '("get", MlsE2EIdConfig)
                    (From 'V5
                     :> (Description ""
                         :> (ZUser
                             :> (Summary "Get config for mlsE2EId"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("mlsE2EId"
                                                             :> Get
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MlsE2EIdConfig))))))))))))
                  :<|> (Named
                          "put-MlsE2EIdConfig@v5"
                          (From 'V5
                           :> (Until 'V6
                               :> (ZUser
                                   :> (Summary "Put config for mlsE2EId"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("mlsE2EId"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (Feature
                                                                                    MlsE2EIdConfig)
                                                                               :> Put
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       MlsE2EIdConfig)))))))))))))))
                        :<|> (Named
                                '("put", MlsE2EIdConfig)
                                (From 'V6
                                 :> (Description ""
                                     :> (ZUser
                                         :> (Summary "Put config for mlsE2EId"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("mlsE2EId"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (Feature
                                                                                          MlsE2EIdConfig)
                                                                                     :> Put
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             MlsE2EIdConfig)))))))))))))))
                              :<|> ((Named
                                       '("get", MlsMigrationConfig)
                                       (From 'V5
                                        :> (Description ""
                                            :> (ZUser
                                                :> (Summary "Get config for mlsMigration"
                                                    :> (CanThrow OperationDenied
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("mlsMigration"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        MlsMigrationConfig))))))))))))
                                     :<|> Named
                                            '("put", MlsMigrationConfig)
                                            (From 'V5
                                             :> (Description ""
                                                 :> (ZUser
                                                     :> (Summary "Put config for mlsMigration"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("mlsMigration"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (Feature
                                                                                                      MlsMigrationConfig)
                                                                                                 :> Put
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         MlsMigrationConfig))))))))))))))))
                                    :<|> ((Named
                                             '("get", EnforceFileDownloadLocationConfig)
                                             (From 'V5
                                              :> (Description
                                                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                  :> (ZUser
                                                      :> (Summary
                                                            "Get config for enforceFileDownloadLocation"
                                                          :> (CanThrow OperationDenied
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("enforceFileDownloadLocation"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              EnforceFileDownloadLocationConfig))))))))))))
                                           :<|> Named
                                                  '("put", EnforceFileDownloadLocationConfig)
                                                  (From 'V5
                                                   :> (Description
                                                         "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                       :> (ZUser
                                                           :> (Summary
                                                                 "Put config for enforceFileDownloadLocation"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> (CanThrow
                                                                                 TeamFeatureError
                                                                               :> (CanThrowMany '[]
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> ("enforceFileDownloadLocation"
                                                                                                   :> (ReqBody
                                                                                                         '[JSON]
                                                                                                         (Feature
                                                                                                            EnforceFileDownloadLocationConfig)
                                                                                                       :> Put
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               EnforceFileDownloadLocationConfig))))))))))))))))
                                          :<|> (Named
                                                  '("get", LimitedEventFanoutConfig)
                                                  (From 'V5
                                                   :> (Description ""
                                                       :> (ZUser
                                                           :> (Summary
                                                                 "Get config for limitedEventFanout"
                                                               :> (CanThrow OperationDenied
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("limitedEventFanout"
                                                                                           :> Get
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   LimitedEventFanoutConfig))))))))))))
                                                :<|> (Named
                                                        "get-all-feature-configs-for-user"
                                                        (Summary "Gets feature configs for a user"
                                                         :> (Description
                                                               "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                             :> (DescriptionOAuthScope
                                                                   'ReadFeatureConfigs
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> Get
                                                                                          '[JSON]
                                                                                          AllTeamFeatures))))))))
                                                      :<|> (Named
                                                              "get-all-feature-configs-for-team"
                                                              (Summary
                                                                 "Gets feature configs for a team"
                                                               :> (Description
                                                                     "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                                   :> (CanThrow 'NotATeamMember
                                                                       :> (CanThrow OperationDenied
                                                                           :> (CanThrow
                                                                                 'TeamNotFound
                                                                               :> (ZLocalUser
                                                                                   :> ("teams"
                                                                                       :> (Capture
                                                                                             "tid"
                                                                                             TeamId
                                                                                           :> ("features"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    AllTeamFeatures)))))))))
                                                            :<|> ((Named
                                                                     '("get-deprecated",
                                                                       SearchVisibilityAvailableConfig)
                                                                     (ZUser
                                                                      :> (Summary
                                                                            "[deprecated] Get config for searchVisibility"
                                                                          :> (Until 'V2
                                                                              :> (Description
                                                                                    "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            OperationDenied
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("search-visibility"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      SearchVisibilityAvailableConfig))))))))))))
                                                                   :<|> (Named
                                                                           '("put-deprecated",
                                                                             SearchVisibilityAvailableConfig)
                                                                           (ZUser
                                                                            :> (Summary
                                                                                  "[deprecated] Get config for searchVisibility"
                                                                                :> (Until 'V2
                                                                                    :> (Description
                                                                                          "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  OperationDenied
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> (CanThrow
                                                                                                          TeamFeatureError
                                                                                                        :> ("teams"
                                                                                                            :> (Capture
                                                                                                                  "tid"
                                                                                                                  TeamId
                                                                                                                :> ("features"
                                                                                                                    :> ("search-visibility"
                                                                                                                        :> (ReqBody
                                                                                                                              '[JSON]
                                                                                                                              (Feature
                                                                                                                                 SearchVisibilityAvailableConfig)
                                                                                                                            :> Put
                                                                                                                                 '[JSON]
                                                                                                                                 (LockableFeature
                                                                                                                                    SearchVisibilityAvailableConfig))))))))))))))
                                                                         :<|> (Named
                                                                                 '("get-deprecated",
                                                                                   ValidateSAMLEmailsConfig)
                                                                                 (ZUser
                                                                                  :> (Summary
                                                                                        "[deprecated] Get config for validateSAMLemails"
                                                                                      :> (Until 'V2
                                                                                          :> (Description
                                                                                                "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                              :> (CanThrow
                                                                                                    'NotATeamMember
                                                                                                  :> (CanThrow
                                                                                                        OperationDenied
                                                                                                      :> (CanThrow
                                                                                                            'TeamNotFound
                                                                                                          :> ("teams"
                                                                                                              :> (Capture
                                                                                                                    "tid"
                                                                                                                    TeamId
                                                                                                                  :> ("features"
                                                                                                                      :> ("validate-saml-emails"
                                                                                                                          :> Get
                                                                                                                               '[JSON]
                                                                                                                               (LockableFeature
                                                                                                                                  ValidateSAMLEmailsConfig))))))))))))
                                                                               :<|> Named
                                                                                      '("get-deprecated",
                                                                                        DigitalSignaturesConfig)
                                                                                      (ZUser
                                                                                       :> (Summary
                                                                                             "[deprecated] Get config for digitalSignatures"
                                                                                           :> (Until
                                                                                                 'V2
                                                                                               :> (Description
                                                                                                     "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("teams"
                                                                                                                   :> (Capture
                                                                                                                         "tid"
                                                                                                                         TeamId
                                                                                                                       :> ("features"
                                                                                                                           :> ("digital-signatures"
                                                                                                                               :> Get
                                                                                                                                    '[JSON]
                                                                                                                                    (LockableFeature
                                                                                                                                       DigitalSignaturesConfig)))))))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            LegalholdConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature legalhold"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("legalhold"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   LegalholdConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  SSOConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature sso"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("sso"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         SSOConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        SearchVisibilityAvailableConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature searchVisibility"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("searchVisibility"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               SearchVisibilityAvailableConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              ValidateSAMLEmailsConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("validateSAMLemails"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     ValidateSAMLEmailsConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    DigitalSignaturesConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature digitalSignatures"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("digitalSignatures"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           DigitalSignaturesConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          AppLockConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature appLock"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("appLock"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 AppLockConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                FileSharingConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature fileSharing"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("fileSharing"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       FileSharingConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      ClassifiedDomainsConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("classifiedDomains"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             ClassifiedDomainsConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            ConferenceCallingConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("conferenceCalling"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   ConferenceCallingConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  SelfDeletingMessagesConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("selfDeletingMessages"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         SelfDeletingMessagesConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        GuestLinksConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               GuestLinksConfig))))))))))
                                                                                                                                    :<|> (Named
                                                                                                                                            '("get-config",
                                                                                                                                              SndFactorPasswordChallengeConfig)
                                                                                                                                            (Summary
                                                                                                                                               "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                             :> (Until
                                                                                                                                                   'V2
                                                                                                                                                 :> (Description
                                                                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                     :> (ZUser
                                                                                                                                                         :> (CanThrow
                                                                                                                                                               'NotATeamMember
                                                                                                                                                             :> (CanThrow
                                                                                                                                                                   OperationDenied
                                                                                                                                                                 :> (CanThrow
                                                                                                                                                                       'TeamNotFound
                                                                                                                                                                     :> ("feature-configs"
                                                                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                                                                             :> Get
                                                                                                                                                                                  '[JSON]
                                                                                                                                                                                  (LockableFeature
                                                                                                                                                                                     SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                          :<|> Named
                                                                                                                                                 '("get-config",
                                                                                                                                                   MLSConfig)
                                                                                                                                                 (Summary
                                                                                                                                                    "[deprecated] Get feature config for feature mls"
                                                                                                                                                  :> (Until
                                                                                                                                                        'V2
                                                                                                                                                      :> (Description
                                                                                                                                                            "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                          :> (ZUser
                                                                                                                                                              :> (CanThrow
                                                                                                                                                                    'NotATeamMember
                                                                                                                                                                  :> (CanThrow
                                                                                                                                                                        OperationDenied
                                                                                                                                                                      :> (CanThrow
                                                                                                                                                                            'TeamNotFound
                                                                                                                                                                          :> ("feature-configs"
                                                                                                                                                                              :> ("mls"
                                                                                                                                                                                  :> Get
                                                                                                                                                                                       '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     '("get", OutlookCalIntegrationConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for outlookCalIntegration"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("outlookCalIntegration"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  OutlookCalIntegrationConfig)))))))))))
   :<|> Named
          '("put", OutlookCalIntegrationConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for outlookCalIntegration"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("outlookCalIntegration"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature OutlookCalIntegrationConfig)
                                                           :> Put
                                                                '[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
     '("get", OutlookCalIntegrationConfig)
     (Description (FeatureAPIDesc OutlookCalIntegrationConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol
                   "Get config for " (FeatureSymbol OutlookCalIntegrationConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol OutlookCalIntegrationConfig
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  OutlookCalIntegrationConfig)))))))))))
   :<|> Named
          '("put", OutlookCalIntegrationConfig)
          (Description (FeatureAPIDesc OutlookCalIntegrationConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol
                        "Put config for " (FeatureSymbol OutlookCalIntegrationConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors OutlookCalIntegrationConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol OutlookCalIntegrationConfig
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature OutlookCalIntegrationConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", OutlookCalIntegrationConfig)
     (Description ""
      :> (ZUser
          :> (Summary "Get config for outlookCalIntegration"
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> ("outlookCalIntegration"
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  OutlookCalIntegrationConfig)))))))))))
   :<|> Named
          '("put", OutlookCalIntegrationConfig)
          (Description ""
           :> (ZUser
               :> (Summary "Put config for outlookCalIntegration"
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany '[]
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("outlookCalIntegration"
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature OutlookCalIntegrationConfig)
                                                           :> Put
                                                                '[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
        '("get", MlsE2EIdConfig)
        (From 'V5
         :> (Description ""
             :> (ZUser
                 :> (Summary "Get config for mlsE2EId"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("mlsE2EId"
                                                 :> Get
                                                      '[JSON]
                                                      (LockableFeature MlsE2EIdConfig))))))))))))
      :<|> (Named
              "put-MlsE2EIdConfig@v5"
              (From 'V5
               :> (Until 'V6
                   :> (ZUser
                       :> (Summary "Put config for mlsE2EId"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("mlsE2EId"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     (Feature MlsE2EIdConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           MlsE2EIdConfig)))))))))))))))
            :<|> (Named
                    '("put", MlsE2EIdConfig)
                    (From 'V6
                     :> (Description ""
                         :> (ZUser
                             :> (Summary "Put config for mlsE2EId"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany '[]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("mlsE2EId"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (Feature MlsE2EIdConfig)
                                                                         :> Put
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 MlsE2EIdConfig)))))))))))))))
                  :<|> ((Named
                           '("get", MlsMigrationConfig)
                           (From 'V5
                            :> (Description ""
                                :> (ZUser
                                    :> (Summary "Get config for mlsMigration"
                                        :> (CanThrow OperationDenied
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("mlsMigration"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            MlsMigrationConfig))))))))))))
                         :<|> Named
                                '("put", MlsMigrationConfig)
                                (From 'V5
                                 :> (Description ""
                                     :> (ZUser
                                         :> (Summary "Put config for mlsMigration"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("mlsMigration"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (Feature
                                                                                          MlsMigrationConfig)
                                                                                     :> Put
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             MlsMigrationConfig))))))))))))))))
                        :<|> ((Named
                                 '("get", EnforceFileDownloadLocationConfig)
                                 (From 'V5
                                  :> (Description
                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                      :> (ZUser
                                          :> (Summary "Get config for enforceFileDownloadLocation"
                                              :> (CanThrow OperationDenied
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("enforceFileDownloadLocation"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  EnforceFileDownloadLocationConfig))))))))))))
                               :<|> Named
                                      '("put", EnforceFileDownloadLocationConfig)
                                      (From 'V5
                                       :> (Description
                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                           :> (ZUser
                                               :> (Summary
                                                     "Put config for enforceFileDownloadLocation"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("enforceFileDownloadLocation"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (Feature
                                                                                                EnforceFileDownloadLocationConfig)
                                                                                           :> Put
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   EnforceFileDownloadLocationConfig))))))))))))))))
                              :<|> (Named
                                      '("get", LimitedEventFanoutConfig)
                                      (From 'V5
                                       :> (Description ""
                                           :> (ZUser
                                               :> (Summary "Get config for limitedEventFanout"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("limitedEventFanout"
                                                                               :> Get
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       LimitedEventFanoutConfig))))))))))))
                                    :<|> (Named
                                            "get-all-feature-configs-for-user"
                                            (Summary "Gets feature configs for a user"
                                             :> (Description
                                                   "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                 :> (DescriptionOAuthScope 'ReadFeatureConfigs
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> Get
                                                                              '[JSON]
                                                                              AllTeamFeatures))))))))
                                          :<|> (Named
                                                  "get-all-feature-configs-for-team"
                                                  (Summary "Gets feature configs for a team"
                                                   :> (Description
                                                         "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (ZLocalUser
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        AllTeamFeatures)))))))))
                                                :<|> ((Named
                                                         '("get-deprecated",
                                                           SearchVisibilityAvailableConfig)
                                                         (ZUser
                                                          :> (Summary
                                                                "[deprecated] Get config for searchVisibility"
                                                              :> (Until 'V2
                                                                  :> (Description
                                                                        "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow
                                                                                OperationDenied
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("search-visibility"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SearchVisibilityAvailableConfig))))))))))))
                                                       :<|> (Named
                                                               '("put-deprecated",
                                                                 SearchVisibilityAvailableConfig)
                                                               (ZUser
                                                                :> (Summary
                                                                      "[deprecated] Get config for searchVisibility"
                                                                    :> (Until 'V2
                                                                        :> (Description
                                                                              "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      OperationDenied
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("search-visibility"
                                                                                                            :> (ReqBody
                                                                                                                  '[JSON]
                                                                                                                  (Feature
                                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                                :> Put
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        SearchVisibilityAvailableConfig))))))))))))))
                                                             :<|> (Named
                                                                     '("get-deprecated",
                                                                       ValidateSAMLEmailsConfig)
                                                                     (ZUser
                                                                      :> (Summary
                                                                            "[deprecated] Get config for validateSAMLemails"
                                                                          :> (Until 'V2
                                                                              :> (Description
                                                                                    "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            OperationDenied
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("validate-saml-emails"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      ValidateSAMLEmailsConfig))))))))))))
                                                                   :<|> Named
                                                                          '("get-deprecated",
                                                                            DigitalSignaturesConfig)
                                                                          (ZUser
                                                                           :> (Summary
                                                                                 "[deprecated] Get config for digitalSignatures"
                                                                               :> (Until 'V2
                                                                                   :> (Description
                                                                                         "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("digital-signatures"
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           DigitalSignaturesConfig)))))))))))))))
                                                      :<|> (Named
                                                              '("get-config", LegalholdConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature legalhold"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("legalhold"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       LegalholdConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config", SSOConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature sso"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("sso"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             SSOConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            SearchVisibilityAvailableConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature searchVisibility"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("searchVisibility"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   SearchVisibilityAvailableConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  ValidateSAMLEmailsConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("validateSAMLemails"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         ValidateSAMLEmailsConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        DigitalSignaturesConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature digitalSignatures"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("digitalSignatures"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               DigitalSignaturesConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              AppLockConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature appLock"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("appLock"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     AppLockConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    FileSharingConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature fileSharing"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("fileSharing"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           FileSharingConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          ClassifiedDomainsConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("classifiedDomains"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 ClassifiedDomainsConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                ConferenceCallingConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("conferenceCalling"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       ConferenceCallingConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      SelfDeletingMessagesConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("selfDeletingMessages"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             SelfDeletingMessagesConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            GuestLinksConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   GuestLinksConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         SndFactorPasswordChallengeConfig))))))))))
                                                                                                                              :<|> Named
                                                                                                                                     '("get-config",
                                                                                                                                       MLSConfig)
                                                                                                                                     (Summary
                                                                                                                                        "[deprecated] Get feature config for feature mls"
                                                                                                                                      :> (Until
                                                                                                                                            'V2
                                                                                                                                          :> (Description
                                                                                                                                                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                              :> (ZUser
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            OperationDenied
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'TeamNotFound
                                                                                                                                                              :> ("feature-configs"
                                                                                                                                                                  :> ("mls"
                                                                                                                                                                      :> Get
                                                                                                                                                                           '[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
         '("get", OutlookCalIntegrationConfig)
         (Description ""
          :> (ZUser
              :> (Summary "Get config for outlookCalIntegration"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("outlookCalIntegration"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      OutlookCalIntegrationConfig)))))))))))
       :<|> Named
              '("put", OutlookCalIntegrationConfig)
              (Description ""
               :> (ZUser
                   :> (Summary "Put config for outlookCalIntegration"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("outlookCalIntegration"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    OutlookCalIntegrationConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       OutlookCalIntegrationConfig)))))))))))))))
      :<|> (Named
              '("get", MlsE2EIdConfig)
              (From 'V5
               :> (Description ""
                   :> (ZUser
                       :> (Summary "Get config for mlsE2EId"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("mlsE2EId"
                                                       :> Get
                                                            '[JSON]
                                                            (LockableFeature
                                                               MlsE2EIdConfig))))))))))))
            :<|> (Named
                    "put-MlsE2EIdConfig@v5"
                    (From 'V5
                     :> (Until 'V6
                         :> (ZUser
                             :> (Summary "Put config for mlsE2EId"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany '[]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("mlsE2EId"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (Feature MlsE2EIdConfig)
                                                                         :> Put
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 MlsE2EIdConfig)))))))))))))))
                  :<|> (Named
                          '("put", MlsE2EIdConfig)
                          (From 'V6
                           :> (Description ""
                               :> (ZUser
                                   :> (Summary "Put config for mlsE2EId"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("mlsE2EId"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (Feature
                                                                                    MlsE2EIdConfig)
                                                                               :> Put
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       MlsE2EIdConfig)))))))))))))))
                        :<|> ((Named
                                 '("get", MlsMigrationConfig)
                                 (From 'V5
                                  :> (Description ""
                                      :> (ZUser
                                          :> (Summary "Get config for mlsMigration"
                                              :> (CanThrow OperationDenied
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("mlsMigration"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  MlsMigrationConfig))))))))))))
                               :<|> Named
                                      '("put", MlsMigrationConfig)
                                      (From 'V5
                                       :> (Description ""
                                           :> (ZUser
                                               :> (Summary "Put config for mlsMigration"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("mlsMigration"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (Feature
                                                                                                MlsMigrationConfig)
                                                                                           :> Put
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   MlsMigrationConfig))))))))))))))))
                              :<|> ((Named
                                       '("get", EnforceFileDownloadLocationConfig)
                                       (From 'V5
                                        :> (Description
                                              "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                            :> (ZUser
                                                :> (Summary
                                                      "Get config for enforceFileDownloadLocation"
                                                    :> (CanThrow OperationDenied
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("enforceFileDownloadLocation"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        EnforceFileDownloadLocationConfig))))))))))))
                                     :<|> Named
                                            '("put", EnforceFileDownloadLocationConfig)
                                            (From 'V5
                                             :> (Description
                                                   "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                                 :> (ZUser
                                                     :> (Summary
                                                           "Put config for enforceFileDownloadLocation"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> (CanThrow TeamFeatureError
                                                                         :> (CanThrowMany '[]
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> ("enforceFileDownloadLocation"
                                                                                             :> (ReqBody
                                                                                                   '[JSON]
                                                                                                   (Feature
                                                                                                      EnforceFileDownloadLocationConfig)
                                                                                                 :> Put
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         EnforceFileDownloadLocationConfig))))))))))))))))
                                    :<|> (Named
                                            '("get", LimitedEventFanoutConfig)
                                            (From 'V5
                                             :> (Description ""
                                                 :> (ZUser
                                                     :> (Summary "Get config for limitedEventFanout"
                                                         :> (CanThrow OperationDenied
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("limitedEventFanout"
                                                                                     :> Get
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             LimitedEventFanoutConfig))))))))))))
                                          :<|> (Named
                                                  "get-all-feature-configs-for-user"
                                                  (Summary "Gets feature configs for a user"
                                                   :> (Description
                                                         "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                       :> (DescriptionOAuthScope 'ReadFeatureConfigs
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> Get
                                                                                    '[JSON]
                                                                                    AllTeamFeatures))))))))
                                                :<|> (Named
                                                        "get-all-feature-configs-for-team"
                                                        (Summary "Gets feature configs for a team"
                                                         :> (Description
                                                               "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                             :> (CanThrow 'NotATeamMember
                                                                 :> (CanThrow OperationDenied
                                                                     :> (CanThrow 'TeamNotFound
                                                                         :> (ZLocalUser
                                                                             :> ("teams"
                                                                                 :> (Capture
                                                                                       "tid" TeamId
                                                                                     :> ("features"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              AllTeamFeatures)))))))))
                                                      :<|> ((Named
                                                               '("get-deprecated",
                                                                 SearchVisibilityAvailableConfig)
                                                               (ZUser
                                                                :> (Summary
                                                                      "[deprecated] Get config for searchVisibility"
                                                                    :> (Until 'V2
                                                                        :> (Description
                                                                              "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      OperationDenied
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("search-visibility"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SearchVisibilityAvailableConfig))))))))))))
                                                             :<|> (Named
                                                                     '("put-deprecated",
                                                                       SearchVisibilityAvailableConfig)
                                                                     (ZUser
                                                                      :> (Summary
                                                                            "[deprecated] Get config for searchVisibility"
                                                                          :> (Until 'V2
                                                                              :> (Description
                                                                                    "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            OperationDenied
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> (CanThrow
                                                                                                    TeamFeatureError
                                                                                                  :> ("teams"
                                                                                                      :> (Capture
                                                                                                            "tid"
                                                                                                            TeamId
                                                                                                          :> ("features"
                                                                                                              :> ("search-visibility"
                                                                                                                  :> (ReqBody
                                                                                                                        '[JSON]
                                                                                                                        (Feature
                                                                                                                           SearchVisibilityAvailableConfig)
                                                                                                                      :> Put
                                                                                                                           '[JSON]
                                                                                                                           (LockableFeature
                                                                                                                              SearchVisibilityAvailableConfig))))))))))))))
                                                                   :<|> (Named
                                                                           '("get-deprecated",
                                                                             ValidateSAMLEmailsConfig)
                                                                           (ZUser
                                                                            :> (Summary
                                                                                  "[deprecated] Get config for validateSAMLemails"
                                                                                :> (Until 'V2
                                                                                    :> (Description
                                                                                          "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                        :> (CanThrow
                                                                                              'NotATeamMember
                                                                                            :> (CanThrow
                                                                                                  OperationDenied
                                                                                                :> (CanThrow
                                                                                                      'TeamNotFound
                                                                                                    :> ("teams"
                                                                                                        :> (Capture
                                                                                                              "tid"
                                                                                                              TeamId
                                                                                                            :> ("features"
                                                                                                                :> ("validate-saml-emails"
                                                                                                                    :> Get
                                                                                                                         '[JSON]
                                                                                                                         (LockableFeature
                                                                                                                            ValidateSAMLEmailsConfig))))))))))))
                                                                         :<|> Named
                                                                                '("get-deprecated",
                                                                                  DigitalSignaturesConfig)
                                                                                (ZUser
                                                                                 :> (Summary
                                                                                       "[deprecated] Get config for digitalSignatures"
                                                                                     :> (Until 'V2
                                                                                         :> (Description
                                                                                               "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("teams"
                                                                                                             :> (Capture
                                                                                                                   "tid"
                                                                                                                   TeamId
                                                                                                                 :> ("features"
                                                                                                                     :> ("digital-signatures"
                                                                                                                         :> Get
                                                                                                                              '[JSON]
                                                                                                                              (LockableFeature
                                                                                                                                 DigitalSignaturesConfig)))))))))))))))
                                                            :<|> (Named
                                                                    '("get-config", LegalholdConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature legalhold"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("legalhold"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             LegalholdConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config", SSOConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature sso"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("sso"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   SSOConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  SearchVisibilityAvailableConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature searchVisibility"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("searchVisibility"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         SearchVisibilityAvailableConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        ValidateSAMLEmailsConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("validateSAMLemails"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               ValidateSAMLEmailsConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              DigitalSignaturesConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature digitalSignatures"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("digitalSignatures"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     DigitalSignaturesConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    AppLockConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature appLock"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("appLock"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           AppLockConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          FileSharingConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature fileSharing"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("fileSharing"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 FileSharingConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                ClassifiedDomainsConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("classifiedDomains"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       ClassifiedDomainsConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      ConferenceCallingConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("conferenceCalling"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             ConferenceCallingConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            SelfDeletingMessagesConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("selfDeletingMessages"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   SelfDeletingMessagesConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  GuestLinksConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("conversationGuestLinks"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         GuestLinksConfig))))))))))
                                                                                                                              :<|> (Named
                                                                                                                                      '("get-config",
                                                                                                                                        SndFactorPasswordChallengeConfig)
                                                                                                                                      (Summary
                                                                                                                                         "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                       :> (Until
                                                                                                                                             'V2
                                                                                                                                           :> (Description
                                                                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                               :> (ZUser
                                                                                                                                                   :> (CanThrow
                                                                                                                                                         'NotATeamMember
                                                                                                                                                       :> (CanThrow
                                                                                                                                                             OperationDenied
                                                                                                                                                           :> (CanThrow
                                                                                                                                                                 'TeamNotFound
                                                                                                                                                               :> ("feature-configs"
                                                                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                                                                       :> Get
                                                                                                                                                                            '[JSON]
                                                                                                                                                                            (LockableFeature
                                                                                                                                                                               SndFactorPasswordChallengeConfig))))))))))
                                                                                                                                    :<|> Named
                                                                                                                                           '("get-config",
                                                                                                                                             MLSConfig)
                                                                                                                                           (Summary
                                                                                                                                              "[deprecated] Get feature config for feature mls"
                                                                                                                                            :> (Until
                                                                                                                                                  'V2
                                                                                                                                                :> (Description
                                                                                                                                                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                                    :> (ZUser
                                                                                                                                                        :> (CanThrow
                                                                                                                                                              'NotATeamMember
                                                                                                                                                            :> (CanThrow
                                                                                                                                                                  OperationDenied
                                                                                                                                                                :> (CanThrow
                                                                                                                                                                      'TeamNotFound
                                                                                                                                                                    :> ("feature-configs"
                                                                                                                                                                        :> ("mls"
                                                                                                                                                                            :> Get
                                                                                                                                                                                 '[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 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", MlsE2EIdConfig) ServerT
  (From 'V5
   :> (Description ""
       :> (ZUser
           :> (Summary "Get config for mlsE2EId"
               :> (CanThrow OperationDenied
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("mlsE2EId"
                                           :> Get
                                                '[JSON] (LockableFeature MlsE2EIdConfig))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (From 'V5
            :> (Description ""
                :> (ZUser
                    :> (Summary "Get config for mlsE2EId"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("mlsE2EId"
                                                    :> Get
                                                         '[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]))
UserId
-> TeamId
-> Sem
     '[Error (Tagged OperationDenied ()),
       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]
     (LockableFeature MlsE2EIdConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member TeamFeatureStore r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member TeamStore r) =>
UserId -> TeamId -> Sem r (LockableFeature cfg)
getFeature
    API
  (Named
     '("get", MlsE2EIdConfig)
     (From 'V5
      :> (Description ""
          :> (ZUser
              :> (Summary "Get config for mlsE2EId"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("mlsE2EId"
                                              :> Get
                                                   '[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
        "put-MlsE2EIdConfig@v5"
        (From 'V5
         :> (Until 'V6
             :> (ZUser
                 :> (Summary "Put config for mlsE2EId"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("mlsE2EId"
                                                         :> (ReqBody
                                                               '[JSON] (Feature MlsE2EIdConfig)
                                                             :> Put
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MlsE2EIdConfig)))))))))))))))
      :<|> (Named
              '("put", MlsE2EIdConfig)
              (From 'V6
               :> (Description ""
                   :> (ZUser
                       :> (Summary "Put config for mlsE2EId"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("mlsE2EId"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     (Feature MlsE2EIdConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           MlsE2EIdConfig)))))))))))))))
            :<|> ((Named
                     '("get", MlsMigrationConfig)
                     (From 'V5
                      :> (Description ""
                          :> (ZUser
                              :> (Summary "Get config for mlsMigration"
                                  :> (CanThrow OperationDenied
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mlsMigration"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      MlsMigrationConfig))))))))))))
                   :<|> Named
                          '("put", MlsMigrationConfig)
                          (From 'V5
                           :> (Description ""
                               :> (ZUser
                                   :> (Summary "Put config for mlsMigration"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("mlsMigration"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (Feature
                                                                                    MlsMigrationConfig)
                                                                               :> Put
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       MlsMigrationConfig))))))))))))))))
                  :<|> ((Named
                           '("get", EnforceFileDownloadLocationConfig)
                           (From 'V5
                            :> (Description
                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                :> (ZUser
                                    :> (Summary "Get config for enforceFileDownloadLocation"
                                        :> (CanThrow OperationDenied
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("enforceFileDownloadLocation"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            EnforceFileDownloadLocationConfig))))))))))))
                         :<|> Named
                                '("put", EnforceFileDownloadLocationConfig)
                                (From 'V5
                                 :> (Description
                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                     :> (ZUser
                                         :> (Summary "Put config for enforceFileDownloadLocation"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("enforceFileDownloadLocation"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (Feature
                                                                                          EnforceFileDownloadLocationConfig)
                                                                                     :> Put
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             EnforceFileDownloadLocationConfig))))))))))))))))
                        :<|> (Named
                                '("get", LimitedEventFanoutConfig)
                                (From 'V5
                                 :> (Description ""
                                     :> (ZUser
                                         :> (Summary "Get config for limitedEventFanout"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("limitedEventFanout"
                                                                         :> Get
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 LimitedEventFanoutConfig))))))))))))
                              :<|> (Named
                                      "get-all-feature-configs-for-user"
                                      (Summary "Gets feature configs for a user"
                                       :> (Description
                                             "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                           :> (DescriptionOAuthScope 'ReadFeatureConfigs
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> Get
                                                                        '[JSON]
                                                                        AllTeamFeatures))))))))
                                    :<|> (Named
                                            "get-all-feature-configs-for-team"
                                            (Summary "Gets feature configs for a team"
                                             :> (Description
                                                   "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (ZLocalUser
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  AllTeamFeatures)))))))))
                                          :<|> ((Named
                                                   '("get-deprecated",
                                                     SearchVisibilityAvailableConfig)
                                                   (ZUser
                                                    :> (Summary
                                                          "[deprecated] Get config for searchVisibility"
                                                        :> (Until 'V2
                                                            :> (Description
                                                                  "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow OperationDenied
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("search-visibility"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SearchVisibilityAvailableConfig))))))))))))
                                                 :<|> (Named
                                                         '("put-deprecated",
                                                           SearchVisibilityAvailableConfig)
                                                         (ZUser
                                                          :> (Summary
                                                                "[deprecated] Get config for searchVisibility"
                                                              :> (Until 'V2
                                                                  :> (Description
                                                                        "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow
                                                                                OperationDenied
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("search-visibility"
                                                                                                      :> (ReqBody
                                                                                                            '[JSON]
                                                                                                            (Feature
                                                                                                               SearchVisibilityAvailableConfig)
                                                                                                          :> Put
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  SearchVisibilityAvailableConfig))))))))))))))
                                                       :<|> (Named
                                                               '("get-deprecated",
                                                                 ValidateSAMLEmailsConfig)
                                                               (ZUser
                                                                :> (Summary
                                                                      "[deprecated] Get config for validateSAMLemails"
                                                                    :> (Until 'V2
                                                                        :> (Description
                                                                              "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      OperationDenied
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("validate-saml-emails"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                ValidateSAMLEmailsConfig))))))))))))
                                                             :<|> Named
                                                                    '("get-deprecated",
                                                                      DigitalSignaturesConfig)
                                                                    (ZUser
                                                                     :> (Summary
                                                                           "[deprecated] Get config for digitalSignatures"
                                                                         :> (Until 'V2
                                                                             :> (Description
                                                                                   "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("digital-signatures"
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     DigitalSignaturesConfig)))))))))))))))
                                                :<|> (Named
                                                        '("get-config", LegalholdConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature legalhold"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("legalhold"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 LegalholdConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config", SSOConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature sso"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("sso"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       SSOConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      SearchVisibilityAvailableConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature searchVisibility"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("searchVisibility"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             SearchVisibilityAvailableConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            ValidateSAMLEmailsConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature validateSAMLemails"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("validateSAMLemails"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   ValidateSAMLEmailsConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  DigitalSignaturesConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature digitalSignatures"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("digitalSignatures"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         DigitalSignaturesConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        AppLockConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature appLock"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("appLock"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               AppLockConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              FileSharingConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature fileSharing"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("fileSharing"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     FileSharingConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    ClassifiedDomainsConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("classifiedDomains"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           ClassifiedDomainsConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          ConferenceCallingConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("conferenceCalling"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 ConferenceCallingConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                SelfDeletingMessagesConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("selfDeletingMessages"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       SelfDeletingMessagesConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      GuestLinksConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             GuestLinksConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   SndFactorPasswordChallengeConfig))))))))))
                                                                                                                        :<|> Named
                                                                                                                               '("get-config",
                                                                                                                                 MLSConfig)
                                                                                                                               (Summary
                                                                                                                                  "[deprecated] Get feature config for feature mls"
                                                                                                                                :> (Until
                                                                                                                                      'V2
                                                                                                                                    :> (Description
                                                                                                                                          "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                        :> (ZUser
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      OperationDenied
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'TeamNotFound
                                                                                                                                                        :> ("feature-configs"
                                                                                                                                                            :> ("mls"
                                                                                                                                                                :> Get
                                                                                                                                                                     '[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
        '("get", MlsE2EIdConfig)
        (From 'V5
         :> (Description ""
             :> (ZUser
                 :> (Summary "Get config for mlsE2EId"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("mlsE2EId"
                                                 :> Get
                                                      '[JSON]
                                                      (LockableFeature MlsE2EIdConfig))))))))))))
      :<|> (Named
              "put-MlsE2EIdConfig@v5"
              (From 'V5
               :> (Until 'V6
                   :> (ZUser
                       :> (Summary "Put config for mlsE2EId"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("mlsE2EId"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     (Feature MlsE2EIdConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           MlsE2EIdConfig)))))))))))))))
            :<|> (Named
                    '("put", MlsE2EIdConfig)
                    (From 'V6
                     :> (Description ""
                         :> (ZUser
                             :> (Summary "Put config for mlsE2EId"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany '[]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("mlsE2EId"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (Feature MlsE2EIdConfig)
                                                                         :> Put
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 MlsE2EIdConfig)))))))))))))))
                  :<|> ((Named
                           '("get", MlsMigrationConfig)
                           (From 'V5
                            :> (Description ""
                                :> (ZUser
                                    :> (Summary "Get config for mlsMigration"
                                        :> (CanThrow OperationDenied
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("mlsMigration"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            MlsMigrationConfig))))))))))))
                         :<|> Named
                                '("put", MlsMigrationConfig)
                                (From 'V5
                                 :> (Description ""
                                     :> (ZUser
                                         :> (Summary "Put config for mlsMigration"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("mlsMigration"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (Feature
                                                                                          MlsMigrationConfig)
                                                                                     :> Put
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             MlsMigrationConfig))))))))))))))))
                        :<|> ((Named
                                 '("get", EnforceFileDownloadLocationConfig)
                                 (From 'V5
                                  :> (Description
                                        "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                      :> (ZUser
                                          :> (Summary "Get config for enforceFileDownloadLocation"
                                              :> (CanThrow OperationDenied
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("enforceFileDownloadLocation"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  EnforceFileDownloadLocationConfig))))))))))))
                               :<|> Named
                                      '("put", EnforceFileDownloadLocationConfig)
                                      (From 'V5
                                       :> (Description
                                             "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                           :> (ZUser
                                               :> (Summary
                                                     "Put config for enforceFileDownloadLocation"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> (CanThrow TeamFeatureError
                                                                   :> (CanThrowMany '[]
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> ("enforceFileDownloadLocation"
                                                                                       :> (ReqBody
                                                                                             '[JSON]
                                                                                             (Feature
                                                                                                EnforceFileDownloadLocationConfig)
                                                                                           :> Put
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   EnforceFileDownloadLocationConfig))))))))))))))))
                              :<|> (Named
                                      '("get", LimitedEventFanoutConfig)
                                      (From 'V5
                                       :> (Description ""
                                           :> (ZUser
                                               :> (Summary "Get config for limitedEventFanout"
                                                   :> (CanThrow OperationDenied
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("limitedEventFanout"
                                                                               :> Get
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       LimitedEventFanoutConfig))))))))))))
                                    :<|> (Named
                                            "get-all-feature-configs-for-user"
                                            (Summary "Gets feature configs for a user"
                                             :> (Description
                                                   "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                                 :> (DescriptionOAuthScope 'ReadFeatureConfigs
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> Get
                                                                              '[JSON]
                                                                              AllTeamFeatures))))))))
                                          :<|> (Named
                                                  "get-all-feature-configs-for-team"
                                                  (Summary "Gets feature configs for a team"
                                                   :> (Description
                                                         "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                       :> (CanThrow 'NotATeamMember
                                                           :> (CanThrow OperationDenied
                                                               :> (CanThrow 'TeamNotFound
                                                                   :> (ZLocalUser
                                                                       :> ("teams"
                                                                           :> (Capture "tid" TeamId
                                                                               :> ("features"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        AllTeamFeatures)))))))))
                                                :<|> ((Named
                                                         '("get-deprecated",
                                                           SearchVisibilityAvailableConfig)
                                                         (ZUser
                                                          :> (Summary
                                                                "[deprecated] Get config for searchVisibility"
                                                              :> (Until 'V2
                                                                  :> (Description
                                                                        "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow
                                                                                OperationDenied
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("search-visibility"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          SearchVisibilityAvailableConfig))))))))))))
                                                       :<|> (Named
                                                               '("put-deprecated",
                                                                 SearchVisibilityAvailableConfig)
                                                               (ZUser
                                                                :> (Summary
                                                                      "[deprecated] Get config for searchVisibility"
                                                                    :> (Until 'V2
                                                                        :> (Description
                                                                              "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      OperationDenied
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> (CanThrow
                                                                                              TeamFeatureError
                                                                                            :> ("teams"
                                                                                                :> (Capture
                                                                                                      "tid"
                                                                                                      TeamId
                                                                                                    :> ("features"
                                                                                                        :> ("search-visibility"
                                                                                                            :> (ReqBody
                                                                                                                  '[JSON]
                                                                                                                  (Feature
                                                                                                                     SearchVisibilityAvailableConfig)
                                                                                                                :> Put
                                                                                                                     '[JSON]
                                                                                                                     (LockableFeature
                                                                                                                        SearchVisibilityAvailableConfig))))))))))))))
                                                             :<|> (Named
                                                                     '("get-deprecated",
                                                                       ValidateSAMLEmailsConfig)
                                                                     (ZUser
                                                                      :> (Summary
                                                                            "[deprecated] Get config for validateSAMLemails"
                                                                          :> (Until 'V2
                                                                              :> (Description
                                                                                    "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                                  :> (CanThrow
                                                                                        'NotATeamMember
                                                                                      :> (CanThrow
                                                                                            OperationDenied
                                                                                          :> (CanThrow
                                                                                                'TeamNotFound
                                                                                              :> ("teams"
                                                                                                  :> (Capture
                                                                                                        "tid"
                                                                                                        TeamId
                                                                                                      :> ("features"
                                                                                                          :> ("validate-saml-emails"
                                                                                                              :> Get
                                                                                                                   '[JSON]
                                                                                                                   (LockableFeature
                                                                                                                      ValidateSAMLEmailsConfig))))))))))))
                                                                   :<|> Named
                                                                          '("get-deprecated",
                                                                            DigitalSignaturesConfig)
                                                                          (ZUser
                                                                           :> (Summary
                                                                                 "[deprecated] Get config for digitalSignatures"
                                                                               :> (Until 'V2
                                                                                   :> (Description
                                                                                         "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("teams"
                                                                                                       :> (Capture
                                                                                                             "tid"
                                                                                                             TeamId
                                                                                                           :> ("features"
                                                                                                               :> ("digital-signatures"
                                                                                                                   :> Get
                                                                                                                        '[JSON]
                                                                                                                        (LockableFeature
                                                                                                                           DigitalSignaturesConfig)))))))))))))))
                                                      :<|> (Named
                                                              '("get-config", LegalholdConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature legalhold"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("legalhold"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       LegalholdConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config", SSOConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature sso"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("sso"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             SSOConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            SearchVisibilityAvailableConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature searchVisibility"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("searchVisibility"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   SearchVisibilityAvailableConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  ValidateSAMLEmailsConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature validateSAMLemails"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("validateSAMLemails"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         ValidateSAMLEmailsConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        DigitalSignaturesConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature digitalSignatures"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("digitalSignatures"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               DigitalSignaturesConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              AppLockConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature appLock"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("appLock"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     AppLockConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    FileSharingConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature fileSharing"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("fileSharing"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           FileSharingConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          ClassifiedDomainsConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("classifiedDomains"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 ClassifiedDomainsConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                ConferenceCallingConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("conferenceCalling"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       ConferenceCallingConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      SelfDeletingMessagesConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("selfDeletingMessages"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             SelfDeletingMessagesConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            GuestLinksConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("conversationGuestLinks"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   GuestLinksConfig))))))))))
                                                                                                                        :<|> (Named
                                                                                                                                '("get-config",
                                                                                                                                  SndFactorPasswordChallengeConfig)
                                                                                                                                (Summary
                                                                                                                                   "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                                 :> (Until
                                                                                                                                       'V2
                                                                                                                                     :> (Description
                                                                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                         :> (ZUser
                                                                                                                                             :> (CanThrow
                                                                                                                                                   'NotATeamMember
                                                                                                                                                 :> (CanThrow
                                                                                                                                                       OperationDenied
                                                                                                                                                     :> (CanThrow
                                                                                                                                                           'TeamNotFound
                                                                                                                                                         :> ("feature-configs"
                                                                                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                                                                                 :> Get
                                                                                                                                                                      '[JSON]
                                                                                                                                                                      (LockableFeature
                                                                                                                                                                         SndFactorPasswordChallengeConfig))))))))))
                                                                                                                              :<|> Named
                                                                                                                                     '("get-config",
                                                                                                                                       MLSConfig)
                                                                                                                                     (Summary
                                                                                                                                        "[deprecated] Get feature config for feature mls"
                                                                                                                                      :> (Until
                                                                                                                                            'V2
                                                                                                                                          :> (Description
                                                                                                                                                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                              :> (ZUser
                                                                                                                                                  :> (CanThrow
                                                                                                                                                        'NotATeamMember
                                                                                                                                                      :> (CanThrow
                                                                                                                                                            OperationDenied
                                                                                                                                                          :> (CanThrow
                                                                                                                                                                'TeamNotFound
                                                                                                                                                              :> ("feature-configs"
                                                                                                                                                                  :> ("mls"
                                                                                                                                                                      :> Get
                                                                                                                                                                           '[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 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-MlsE2EIdConfig@v5" ServerT
  (From 'V5
   :> (Until 'V6
       :> (ZUser
           :> (Summary "Put config for mlsE2EId"
               :> (CanThrow OperationDenied
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> (CanThrow TeamFeatureError
                               :> (CanThrowMany '[]
                                   :> ("teams"
                                       :> (Capture "tid" TeamId
                                           :> ("features"
                                               :> ("mlsE2EId"
                                                   :> (ReqBody '[JSON] (Feature MlsE2EIdConfig)
                                                       :> Put
                                                            '[JSON]
                                                            (LockableFeature
                                                               MlsE2EIdConfig)))))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (From 'V5
            :> (Until 'V6
                :> (ZUser
                    :> (Summary "Put config for mlsE2EId"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> (CanThrow TeamFeatureError
                                        :> (CanThrowMany '[]
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("mlsE2EId"
                                                            :> (ReqBody
                                                                  '[JSON] (Feature MlsE2EIdConfig)
                                                                :> Put
                                                                     '[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]))
UserId
-> TeamId
-> Feature MlsE2EIdConfig
-> Sem
     '[Error (Tagged OperationDenied ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'TeamNotFound ()),
       Error TeamFeatureError, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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)
forall cfg (r :: EffectRow).
(SetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 SetFeatureForTeamConstraints cfg r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member (Error TeamFeatureError) r, Member (Input Opts) r,
 Member TeamStore r, Member TeamFeatureStore r,
 Member (Logger (Msg -> Msg)) r, Member NotificationSubsystem r) =>
UserId -> TeamId -> Feature cfg -> Sem r (LockableFeature cfg)
setFeature
    API
  (Named
     "put-MlsE2EIdConfig@v5"
     (From 'V5
      :> (Until 'V6
          :> (ZUser
              :> (Summary "Put config for mlsE2EId"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> (CanThrow TeamFeatureError
                                  :> (CanThrowMany '[]
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("mlsE2EId"
                                                      :> (ReqBody '[JSON] (Feature MlsE2EIdConfig)
                                                          :> Put
                                                               '[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
        '("put", MlsE2EIdConfig)
        (From 'V6
         :> (Description ""
             :> (ZUser
                 :> (Summary "Put config for mlsE2EId"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("mlsE2EId"
                                                         :> (ReqBody
                                                               '[JSON] (Feature MlsE2EIdConfig)
                                                             :> Put
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MlsE2EIdConfig)))))))))))))))
      :<|> ((Named
               '("get", MlsMigrationConfig)
               (From 'V5
                :> (Description ""
                    :> (ZUser
                        :> (Summary "Get config for mlsMigration"
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("mlsMigration"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature
                                                                MlsMigrationConfig))))))))))))
             :<|> Named
                    '("put", MlsMigrationConfig)
                    (From 'V5
                     :> (Description ""
                         :> (ZUser
                             :> (Summary "Put config for mlsMigration"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany '[]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("mlsMigration"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (Feature
                                                                              MlsMigrationConfig)
                                                                         :> Put
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 MlsMigrationConfig))))))))))))))))
            :<|> ((Named
                     '("get", EnforceFileDownloadLocationConfig)
                     (From 'V5
                      :> (Description
                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                          :> (ZUser
                              :> (Summary "Get config for enforceFileDownloadLocation"
                                  :> (CanThrow OperationDenied
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("enforceFileDownloadLocation"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      EnforceFileDownloadLocationConfig))))))))))))
                   :<|> Named
                          '("put", EnforceFileDownloadLocationConfig)
                          (From 'V5
                           :> (Description
                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                               :> (ZUser
                                   :> (Summary "Put config for enforceFileDownloadLocation"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("enforceFileDownloadLocation"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (Feature
                                                                                    EnforceFileDownloadLocationConfig)
                                                                               :> Put
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       EnforceFileDownloadLocationConfig))))))))))))))))
                  :<|> (Named
                          '("get", LimitedEventFanoutConfig)
                          (From 'V5
                           :> (Description ""
                               :> (ZUser
                                   :> (Summary "Get config for limitedEventFanout"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("limitedEventFanout"
                                                                   :> Get
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           LimitedEventFanoutConfig))))))))))))
                        :<|> (Named
                                "get-all-feature-configs-for-user"
                                (Summary "Gets feature configs for a user"
                                 :> (Description
                                       "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                     :> (DescriptionOAuthScope 'ReadFeatureConfigs
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> Get '[JSON] AllTeamFeatures))))))))
                              :<|> (Named
                                      "get-all-feature-configs-for-team"
                                      (Summary "Gets feature configs for a team"
                                       :> (Description
                                             "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (ZLocalUser
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> Get
                                                                            '[JSON]
                                                                            AllTeamFeatures)))))))))
                                    :<|> ((Named
                                             '("get-deprecated", SearchVisibilityAvailableConfig)
                                             (ZUser
                                              :> (Summary
                                                    "[deprecated] Get config for searchVisibility"
                                                  :> (Until 'V2
                                                      :> (Description
                                                            "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow OperationDenied
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("search-visibility"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SearchVisibilityAvailableConfig))))))))))))
                                           :<|> (Named
                                                   '("put-deprecated",
                                                     SearchVisibilityAvailableConfig)
                                                   (ZUser
                                                    :> (Summary
                                                          "[deprecated] Get config for searchVisibility"
                                                        :> (Until 'V2
                                                            :> (Description
                                                                  "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow OperationDenied
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("search-visibility"
                                                                                                :> (ReqBody
                                                                                                      '[JSON]
                                                                                                      (Feature
                                                                                                         SearchVisibilityAvailableConfig)
                                                                                                    :> Put
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            SearchVisibilityAvailableConfig))))))))))))))
                                                 :<|> (Named
                                                         '("get-deprecated",
                                                           ValidateSAMLEmailsConfig)
                                                         (ZUser
                                                          :> (Summary
                                                                "[deprecated] Get config for validateSAMLemails"
                                                              :> (Until 'V2
                                                                  :> (Description
                                                                        "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow
                                                                                OperationDenied
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("validate-saml-emails"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          ValidateSAMLEmailsConfig))))))))))))
                                                       :<|> Named
                                                              '("get-deprecated",
                                                                DigitalSignaturesConfig)
                                                              (ZUser
                                                               :> (Summary
                                                                     "[deprecated] Get config for digitalSignatures"
                                                                   :> (Until 'V2
                                                                       :> (Description
                                                                             "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("digital-signatures"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               DigitalSignaturesConfig)))))))))))))))
                                          :<|> (Named
                                                  '("get-config", LegalholdConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature legalhold"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("legalhold"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           LegalholdConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", SSOConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature sso"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("sso"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 SSOConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                SearchVisibilityAvailableConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature searchVisibility"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("searchVisibility"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       SearchVisibilityAvailableConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      ValidateSAMLEmailsConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature validateSAMLemails"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("validateSAMLemails"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             ValidateSAMLEmailsConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            DigitalSignaturesConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature digitalSignatures"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("digitalSignatures"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   DigitalSignaturesConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  AppLockConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature appLock"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("appLock"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         AppLockConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        FileSharingConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature fileSharing"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("fileSharing"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               FileSharingConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              ClassifiedDomainsConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature classifiedDomains"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("classifiedDomains"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     ClassifiedDomainsConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    ConferenceCallingConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("conferenceCalling"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           ConferenceCallingConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          SelfDeletingMessagesConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("selfDeletingMessages"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 SelfDeletingMessagesConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                GuestLinksConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       GuestLinksConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             SndFactorPasswordChallengeConfig))))))))))
                                                                                                                  :<|> Named
                                                                                                                         '("get-config",
                                                                                                                           MLSConfig)
                                                                                                                         (Summary
                                                                                                                            "[deprecated] Get feature config for feature mls"
                                                                                                                          :> (Until
                                                                                                                                'V2
                                                                                                                              :> (Description
                                                                                                                                    "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                  :> (ZUser
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                OperationDenied
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'TeamNotFound
                                                                                                                                                  :> ("feature-configs"
                                                                                                                                                      :> ("mls"
                                                                                                                                                          :> Get
                                                                                                                                                               '[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
        "put-MlsE2EIdConfig@v5"
        (From 'V5
         :> (Until 'V6
             :> (ZUser
                 :> (Summary "Put config for mlsE2EId"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("mlsE2EId"
                                                         :> (ReqBody
                                                               '[JSON] (Feature MlsE2EIdConfig)
                                                             :> Put
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MlsE2EIdConfig)))))))))))))))
      :<|> (Named
              '("put", MlsE2EIdConfig)
              (From 'V6
               :> (Description ""
                   :> (ZUser
                       :> (Summary "Put config for mlsE2EId"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("mlsE2EId"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     (Feature MlsE2EIdConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           MlsE2EIdConfig)))))))))))))))
            :<|> ((Named
                     '("get", MlsMigrationConfig)
                     (From 'V5
                      :> (Description ""
                          :> (ZUser
                              :> (Summary "Get config for mlsMigration"
                                  :> (CanThrow OperationDenied
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mlsMigration"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      MlsMigrationConfig))))))))))))
                   :<|> Named
                          '("put", MlsMigrationConfig)
                          (From 'V5
                           :> (Description ""
                               :> (ZUser
                                   :> (Summary "Put config for mlsMigration"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("mlsMigration"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (Feature
                                                                                    MlsMigrationConfig)
                                                                               :> Put
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       MlsMigrationConfig))))))))))))))))
                  :<|> ((Named
                           '("get", EnforceFileDownloadLocationConfig)
                           (From 'V5
                            :> (Description
                                  "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                :> (ZUser
                                    :> (Summary "Get config for enforceFileDownloadLocation"
                                        :> (CanThrow OperationDenied
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("enforceFileDownloadLocation"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            EnforceFileDownloadLocationConfig))))))))))))
                         :<|> Named
                                '("put", EnforceFileDownloadLocationConfig)
                                (From 'V5
                                 :> (Description
                                       "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                                     :> (ZUser
                                         :> (Summary "Put config for enforceFileDownloadLocation"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> (CanThrow TeamFeatureError
                                                             :> (CanThrowMany '[]
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> ("enforceFileDownloadLocation"
                                                                                 :> (ReqBody
                                                                                       '[JSON]
                                                                                       (Feature
                                                                                          EnforceFileDownloadLocationConfig)
                                                                                     :> Put
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             EnforceFileDownloadLocationConfig))))))))))))))))
                        :<|> (Named
                                '("get", LimitedEventFanoutConfig)
                                (From 'V5
                                 :> (Description ""
                                     :> (ZUser
                                         :> (Summary "Get config for limitedEventFanout"
                                             :> (CanThrow OperationDenied
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("limitedEventFanout"
                                                                         :> Get
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 LimitedEventFanoutConfig))))))))))))
                              :<|> (Named
                                      "get-all-feature-configs-for-user"
                                      (Summary "Gets feature configs for a user"
                                       :> (Description
                                             "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                           :> (DescriptionOAuthScope 'ReadFeatureConfigs
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> Get
                                                                        '[JSON]
                                                                        AllTeamFeatures))))))))
                                    :<|> (Named
                                            "get-all-feature-configs-for-team"
                                            (Summary "Gets feature configs for a team"
                                             :> (Description
                                                   "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                                 :> (CanThrow 'NotATeamMember
                                                     :> (CanThrow OperationDenied
                                                         :> (CanThrow 'TeamNotFound
                                                             :> (ZLocalUser
                                                                 :> ("teams"
                                                                     :> (Capture "tid" TeamId
                                                                         :> ("features"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  AllTeamFeatures)))))))))
                                          :<|> ((Named
                                                   '("get-deprecated",
                                                     SearchVisibilityAvailableConfig)
                                                   (ZUser
                                                    :> (Summary
                                                          "[deprecated] Get config for searchVisibility"
                                                        :> (Until 'V2
                                                            :> (Description
                                                                  "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow OperationDenied
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("search-visibility"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SearchVisibilityAvailableConfig))))))))))))
                                                 :<|> (Named
                                                         '("put-deprecated",
                                                           SearchVisibilityAvailableConfig)
                                                         (ZUser
                                                          :> (Summary
                                                                "[deprecated] Get config for searchVisibility"
                                                              :> (Until 'V2
                                                                  :> (Description
                                                                        "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow
                                                                                OperationDenied
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> (CanThrow
                                                                                        TeamFeatureError
                                                                                      :> ("teams"
                                                                                          :> (Capture
                                                                                                "tid"
                                                                                                TeamId
                                                                                              :> ("features"
                                                                                                  :> ("search-visibility"
                                                                                                      :> (ReqBody
                                                                                                            '[JSON]
                                                                                                            (Feature
                                                                                                               SearchVisibilityAvailableConfig)
                                                                                                          :> Put
                                                                                                               '[JSON]
                                                                                                               (LockableFeature
                                                                                                                  SearchVisibilityAvailableConfig))))))))))))))
                                                       :<|> (Named
                                                               '("get-deprecated",
                                                                 ValidateSAMLEmailsConfig)
                                                               (ZUser
                                                                :> (Summary
                                                                      "[deprecated] Get config for validateSAMLemails"
                                                                    :> (Until 'V2
                                                                        :> (Description
                                                                              "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                            :> (CanThrow
                                                                                  'NotATeamMember
                                                                                :> (CanThrow
                                                                                      OperationDenied
                                                                                    :> (CanThrow
                                                                                          'TeamNotFound
                                                                                        :> ("teams"
                                                                                            :> (Capture
                                                                                                  "tid"
                                                                                                  TeamId
                                                                                                :> ("features"
                                                                                                    :> ("validate-saml-emails"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                ValidateSAMLEmailsConfig))))))))))))
                                                             :<|> Named
                                                                    '("get-deprecated",
                                                                      DigitalSignaturesConfig)
                                                                    (ZUser
                                                                     :> (Summary
                                                                           "[deprecated] Get config for digitalSignatures"
                                                                         :> (Until 'V2
                                                                             :> (Description
                                                                                   "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("teams"
                                                                                                 :> (Capture
                                                                                                       "tid"
                                                                                                       TeamId
                                                                                                     :> ("features"
                                                                                                         :> ("digital-signatures"
                                                                                                             :> Get
                                                                                                                  '[JSON]
                                                                                                                  (LockableFeature
                                                                                                                     DigitalSignaturesConfig)))))))))))))))
                                                :<|> (Named
                                                        '("get-config", LegalholdConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature legalhold"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("legalhold"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 LegalholdConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config", SSOConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature sso"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("sso"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       SSOConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      SearchVisibilityAvailableConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature searchVisibility"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("searchVisibility"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             SearchVisibilityAvailableConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            ValidateSAMLEmailsConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature validateSAMLemails"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("validateSAMLemails"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   ValidateSAMLEmailsConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  DigitalSignaturesConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature digitalSignatures"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("digitalSignatures"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         DigitalSignaturesConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        AppLockConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature appLock"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("appLock"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               AppLockConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              FileSharingConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature fileSharing"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("fileSharing"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     FileSharingConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    ClassifiedDomainsConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature classifiedDomains"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("classifiedDomains"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           ClassifiedDomainsConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          ConferenceCallingConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("conferenceCalling"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 ConferenceCallingConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                SelfDeletingMessagesConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("selfDeletingMessages"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       SelfDeletingMessagesConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      GuestLinksConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("conversationGuestLinks"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             GuestLinksConfig))))))))))
                                                                                                                  :<|> (Named
                                                                                                                          '("get-config",
                                                                                                                            SndFactorPasswordChallengeConfig)
                                                                                                                          (Summary
                                                                                                                             "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                           :> (Until
                                                                                                                                 'V2
                                                                                                                               :> (Description
                                                                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                   :> (ZUser
                                                                                                                                       :> (CanThrow
                                                                                                                                             'NotATeamMember
                                                                                                                                           :> (CanThrow
                                                                                                                                                 OperationDenied
                                                                                                                                               :> (CanThrow
                                                                                                                                                     'TeamNotFound
                                                                                                                                                   :> ("feature-configs"
                                                                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                                                                           :> Get
                                                                                                                                                                '[JSON]
                                                                                                                                                                (LockableFeature
                                                                                                                                                                   SndFactorPasswordChallengeConfig))))))))))
                                                                                                                        :<|> Named
                                                                                                                               '("get-config",
                                                                                                                                 MLSConfig)
                                                                                                                               (Summary
                                                                                                                                  "[deprecated] Get feature config for feature mls"
                                                                                                                                :> (Until
                                                                                                                                      'V2
                                                                                                                                    :> (Description
                                                                                                                                          "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                        :> (ZUser
                                                                                                                                            :> (CanThrow
                                                                                                                                                  'NotATeamMember
                                                                                                                                                :> (CanThrow
                                                                                                                                                      OperationDenied
                                                                                                                                                    :> (CanThrow
                                                                                                                                                          'TeamNotFound
                                                                                                                                                        :> ("feature-configs"
                                                                                                                                                            :> ("mls"
                                                                                                                                                                :> Get
                                                                                                                                                                     '[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 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", MlsE2EIdConfig) ((UserId
 -> TeamId
 -> Feature MlsE2EIdConfig
 -> Sem
      '[Error (Tagged OperationDenied ()),
        Error (Tagged 'NotATeamMember ()), Error (Tagged 'TeamNotFound ()),
        Error TeamFeatureError, BrigAccess, SparAccess,
        NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
        FederatorAccess, BackendNotificationQueueAccess, BotAccess,
        FireAndForget, ClientStore, CodeStore, ProposalStore,
        ConversationStore, SubConversationStore, Random,
        CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
        SearchVisibilityStore, ServiceStore, TeamNotificationStore,
        TeamStore, TeamMemberStore InternalPaging,
        TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
        ListItems CassandraPaging (Remote ConvId),
        ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
        ListItems InternalPaging TeamId, Input AllTeamFeatures,
        Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
        Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
        Logger (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))
-> UserId
-> TeamId
-> Feature MlsE2EIdConfig
-> Sem
     '[Error (Tagged OperationDenied ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'TeamNotFound ()),
       Error TeamFeatureError, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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)
forall (r :: EffectRow) a.
Member (Error TeamFeatureError) r =>
(UserId -> TeamId -> Feature MlsE2EIdConfig -> Sem r a)
-> UserId -> TeamId -> Feature MlsE2EIdConfig -> Sem r a
guardMlsE2EIdConfig UserId
-> TeamId
-> Feature MlsE2EIdConfig
-> Sem
     '[Error (Tagged OperationDenied ()),
       Error (Tagged 'NotATeamMember ()), Error (Tagged 'TeamNotFound ()),
       Error TeamFeatureError, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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)
forall cfg (r :: EffectRow).
(SetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 SetFeatureForTeamConstraints cfg r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member (Error TeamFeatureError) r, Member (Input Opts) r,
 Member TeamStore r, Member TeamFeatureStore r,
 Member (Logger (Msg -> Msg)) r, Member NotificationSubsystem r) =>
UserId -> TeamId -> Feature cfg -> Sem r (LockableFeature cfg)
setFeature)
    API
  (Named
     '("put", MlsE2EIdConfig)
     (From 'V6
      :> (Description ""
          :> (ZUser
              :> (Summary "Put config for mlsE2EId"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> (CanThrow TeamFeatureError
                                  :> (CanThrowMany '[]
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("mlsE2EId"
                                                      :> (ReqBody '[JSON] (Feature MlsE2EIdConfig)
                                                          :> Put
                                                               '[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
         '("get", MlsMigrationConfig)
         (From 'V5
          :> (Description ""
              :> (ZUser
                  :> (Summary "Get config for mlsMigration"
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("mlsMigration"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature
                                                          MlsMigrationConfig))))))))))))
       :<|> Named
              '("put", MlsMigrationConfig)
              (From 'V5
               :> (Description ""
                   :> (ZUser
                       :> (Summary "Put config for mlsMigration"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("mlsMigration"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     (Feature MlsMigrationConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           MlsMigrationConfig))))))))))))))))
      :<|> ((Named
               '("get", EnforceFileDownloadLocationConfig)
               (From 'V5
                :> (Description
                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                    :> (ZUser
                        :> (Summary "Get config for enforceFileDownloadLocation"
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("enforceFileDownloadLocation"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature
                                                                EnforceFileDownloadLocationConfig))))))))))))
             :<|> Named
                    '("put", EnforceFileDownloadLocationConfig)
                    (From 'V5
                     :> (Description
                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                         :> (ZUser
                             :> (Summary "Put config for enforceFileDownloadLocation"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany '[]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("enforceFileDownloadLocation"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (Feature
                                                                              EnforceFileDownloadLocationConfig)
                                                                         :> Put
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 EnforceFileDownloadLocationConfig))))))))))))))))
            :<|> (Named
                    '("get", LimitedEventFanoutConfig)
                    (From 'V5
                     :> (Description ""
                         :> (ZUser
                             :> (Summary "Get config for limitedEventFanout"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("limitedEventFanout"
                                                             :> Get
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     LimitedEventFanoutConfig))))))))))))
                  :<|> (Named
                          "get-all-feature-configs-for-user"
                          (Summary "Gets feature configs for a user"
                           :> (Description
                                 "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                               :> (DescriptionOAuthScope 'ReadFeatureConfigs
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> Get '[JSON] AllTeamFeatures))))))))
                        :<|> (Named
                                "get-all-feature-configs-for-team"
                                (Summary "Gets feature configs for a team"
                                 :> (Description
                                       "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'TeamNotFound
                                                 :> (ZLocalUser
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> Get
                                                                      '[JSON]
                                                                      AllTeamFeatures)))))))))
                              :<|> ((Named
                                       '("get-deprecated", SearchVisibilityAvailableConfig)
                                       (ZUser
                                        :> (Summary "[deprecated] Get config for searchVisibility"
                                            :> (Until 'V2
                                                :> (Description
                                                      "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow OperationDenied
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("search-visibility"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SearchVisibilityAvailableConfig))))))))))))
                                     :<|> (Named
                                             '("put-deprecated", SearchVisibilityAvailableConfig)
                                             (ZUser
                                              :> (Summary
                                                    "[deprecated] Get config for searchVisibility"
                                                  :> (Until 'V2
                                                      :> (Description
                                                            "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow OperationDenied
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("search-visibility"
                                                                                          :> (ReqBody
                                                                                                '[JSON]
                                                                                                (Feature
                                                                                                   SearchVisibilityAvailableConfig)
                                                                                              :> Put
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      SearchVisibilityAvailableConfig))))))))))))))
                                           :<|> (Named
                                                   '("get-deprecated", ValidateSAMLEmailsConfig)
                                                   (ZUser
                                                    :> (Summary
                                                          "[deprecated] Get config for validateSAMLemails"
                                                        :> (Until 'V2
                                                            :> (Description
                                                                  "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow OperationDenied
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("validate-saml-emails"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    ValidateSAMLEmailsConfig))))))))))))
                                                 :<|> Named
                                                        '("get-deprecated", DigitalSignaturesConfig)
                                                        (ZUser
                                                         :> (Summary
                                                               "[deprecated] Get config for digitalSignatures"
                                                             :> (Until 'V2
                                                                 :> (Description
                                                                       "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("digital-signatures"
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         DigitalSignaturesConfig)))))))))))))))
                                    :<|> (Named
                                            '("get-config", LegalholdConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature legalhold"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("legalhold"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     LegalholdConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", SSOConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature sso"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("sso"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           SSOConfig))))))))))
                                                :<|> (Named
                                                        '("get-config",
                                                          SearchVisibilityAvailableConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature searchVisibility"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("searchVisibility"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 SearchVisibilityAvailableConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                ValidateSAMLEmailsConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature validateSAMLemails"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("validateSAMLemails"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       ValidateSAMLEmailsConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      DigitalSignaturesConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature digitalSignatures"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("digitalSignatures"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             DigitalSignaturesConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            AppLockConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature appLock"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("appLock"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   AppLockConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  FileSharingConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature fileSharing"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("fileSharing"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         FileSharingConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        ClassifiedDomainsConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature classifiedDomains"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("classifiedDomains"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               ClassifiedDomainsConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              ConferenceCallingConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature conferenceCalling"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("conferenceCalling"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     ConferenceCallingConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    SelfDeletingMessagesConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("selfDeletingMessages"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           SelfDeletingMessagesConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          GuestLinksConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 GuestLinksConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       SndFactorPasswordChallengeConfig))))))))))
                                                                                                            :<|> Named
                                                                                                                   '("get-config",
                                                                                                                     MLSConfig)
                                                                                                                   (Summary
                                                                                                                      "[deprecated] Get feature config for feature mls"
                                                                                                                    :> (Until
                                                                                                                          'V2
                                                                                                                        :> (Description
                                                                                                                              "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                            :> (ZUser
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          OperationDenied
                                                                                                                                        :> (CanThrow
                                                                                                                                              'TeamNotFound
                                                                                                                                            :> ("feature-configs"
                                                                                                                                                :> ("mls"
                                                                                                                                                    :> Get
                                                                                                                                                         '[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
        '("put", MlsE2EIdConfig)
        (From 'V6
         :> (Description ""
             :> (ZUser
                 :> (Summary "Put config for mlsE2EId"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> (CanThrowMany '[]
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> ("mlsE2EId"
                                                         :> (ReqBody
                                                               '[JSON] (Feature MlsE2EIdConfig)
                                                             :> Put
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     MlsE2EIdConfig)))))))))))))))
      :<|> ((Named
               '("get", MlsMigrationConfig)
               (From 'V5
                :> (Description ""
                    :> (ZUser
                        :> (Summary "Get config for mlsMigration"
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("mlsMigration"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature
                                                                MlsMigrationConfig))))))))))))
             :<|> Named
                    '("put", MlsMigrationConfig)
                    (From 'V5
                     :> (Description ""
                         :> (ZUser
                             :> (Summary "Put config for mlsMigration"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany '[]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("mlsMigration"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (Feature
                                                                              MlsMigrationConfig)
                                                                         :> Put
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 MlsMigrationConfig))))))))))))))))
            :<|> ((Named
                     '("get", EnforceFileDownloadLocationConfig)
                     (From 'V5
                      :> (Description
                            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                          :> (ZUser
                              :> (Summary "Get config for enforceFileDownloadLocation"
                                  :> (CanThrow OperationDenied
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("enforceFileDownloadLocation"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      EnforceFileDownloadLocationConfig))))))))))))
                   :<|> Named
                          '("put", EnforceFileDownloadLocationConfig)
                          (From 'V5
                           :> (Description
                                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                               :> (ZUser
                                   :> (Summary "Put config for enforceFileDownloadLocation"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> (CanThrow TeamFeatureError
                                                       :> (CanThrowMany '[]
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> ("enforceFileDownloadLocation"
                                                                           :> (ReqBody
                                                                                 '[JSON]
                                                                                 (Feature
                                                                                    EnforceFileDownloadLocationConfig)
                                                                               :> Put
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       EnforceFileDownloadLocationConfig))))))))))))))))
                  :<|> (Named
                          '("get", LimitedEventFanoutConfig)
                          (From 'V5
                           :> (Description ""
                               :> (ZUser
                                   :> (Summary "Get config for limitedEventFanout"
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("limitedEventFanout"
                                                                   :> Get
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           LimitedEventFanoutConfig))))))))))))
                        :<|> (Named
                                "get-all-feature-configs-for-user"
                                (Summary "Gets feature configs for a user"
                                 :> (Description
                                       "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                                     :> (DescriptionOAuthScope 'ReadFeatureConfigs
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> Get '[JSON] AllTeamFeatures))))))))
                              :<|> (Named
                                      "get-all-feature-configs-for-team"
                                      (Summary "Gets feature configs for a team"
                                       :> (Description
                                             "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                           :> (CanThrow 'NotATeamMember
                                               :> (CanThrow OperationDenied
                                                   :> (CanThrow 'TeamNotFound
                                                       :> (ZLocalUser
                                                           :> ("teams"
                                                               :> (Capture "tid" TeamId
                                                                   :> ("features"
                                                                       :> Get
                                                                            '[JSON]
                                                                            AllTeamFeatures)))))))))
                                    :<|> ((Named
                                             '("get-deprecated", SearchVisibilityAvailableConfig)
                                             (ZUser
                                              :> (Summary
                                                    "[deprecated] Get config for searchVisibility"
                                                  :> (Until 'V2
                                                      :> (Description
                                                            "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow OperationDenied
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("search-visibility"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              SearchVisibilityAvailableConfig))))))))))))
                                           :<|> (Named
                                                   '("put-deprecated",
                                                     SearchVisibilityAvailableConfig)
                                                   (ZUser
                                                    :> (Summary
                                                          "[deprecated] Get config for searchVisibility"
                                                        :> (Until 'V2
                                                            :> (Description
                                                                  "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow OperationDenied
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> (CanThrow
                                                                                  TeamFeatureError
                                                                                :> ("teams"
                                                                                    :> (Capture
                                                                                          "tid"
                                                                                          TeamId
                                                                                        :> ("features"
                                                                                            :> ("search-visibility"
                                                                                                :> (ReqBody
                                                                                                      '[JSON]
                                                                                                      (Feature
                                                                                                         SearchVisibilityAvailableConfig)
                                                                                                    :> Put
                                                                                                         '[JSON]
                                                                                                         (LockableFeature
                                                                                                            SearchVisibilityAvailableConfig))))))))))))))
                                                 :<|> (Named
                                                         '("get-deprecated",
                                                           ValidateSAMLEmailsConfig)
                                                         (ZUser
                                                          :> (Summary
                                                                "[deprecated] Get config for validateSAMLemails"
                                                              :> (Until 'V2
                                                                  :> (Description
                                                                        "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                      :> (CanThrow 'NotATeamMember
                                                                          :> (CanThrow
                                                                                OperationDenied
                                                                              :> (CanThrow
                                                                                    'TeamNotFound
                                                                                  :> ("teams"
                                                                                      :> (Capture
                                                                                            "tid"
                                                                                            TeamId
                                                                                          :> ("features"
                                                                                              :> ("validate-saml-emails"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          ValidateSAMLEmailsConfig))))))))))))
                                                       :<|> Named
                                                              '("get-deprecated",
                                                                DigitalSignaturesConfig)
                                                              (ZUser
                                                               :> (Summary
                                                                     "[deprecated] Get config for digitalSignatures"
                                                                   :> (Until 'V2
                                                                       :> (Description
                                                                             "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("teams"
                                                                                           :> (Capture
                                                                                                 "tid"
                                                                                                 TeamId
                                                                                               :> ("features"
                                                                                                   :> ("digital-signatures"
                                                                                                       :> Get
                                                                                                            '[JSON]
                                                                                                            (LockableFeature
                                                                                                               DigitalSignaturesConfig)))))))))))))))
                                          :<|> (Named
                                                  '("get-config", LegalholdConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature legalhold"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("legalhold"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           LegalholdConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", SSOConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature sso"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("sso"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 SSOConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                SearchVisibilityAvailableConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature searchVisibility"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("searchVisibility"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       SearchVisibilityAvailableConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      ValidateSAMLEmailsConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature validateSAMLemails"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("validateSAMLemails"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             ValidateSAMLEmailsConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            DigitalSignaturesConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature digitalSignatures"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("digitalSignatures"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   DigitalSignaturesConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  AppLockConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature appLock"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("appLock"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         AppLockConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        FileSharingConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature fileSharing"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("fileSharing"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               FileSharingConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              ClassifiedDomainsConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature classifiedDomains"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("classifiedDomains"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     ClassifiedDomainsConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    ConferenceCallingConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature conferenceCalling"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("conferenceCalling"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           ConferenceCallingConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          SelfDeletingMessagesConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("selfDeletingMessages"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 SelfDeletingMessagesConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                GuestLinksConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("conversationGuestLinks"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       GuestLinksConfig))))))))))
                                                                                                            :<|> (Named
                                                                                                                    '("get-config",
                                                                                                                      SndFactorPasswordChallengeConfig)
                                                                                                                    (Summary
                                                                                                                       "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                                     :> (Until
                                                                                                                           'V2
                                                                                                                         :> (Description
                                                                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                             :> (ZUser
                                                                                                                                 :> (CanThrow
                                                                                                                                       'NotATeamMember
                                                                                                                                     :> (CanThrow
                                                                                                                                           OperationDenied
                                                                                                                                         :> (CanThrow
                                                                                                                                               'TeamNotFound
                                                                                                                                             :> ("feature-configs"
                                                                                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                                                                                     :> Get
                                                                                                                                                          '[JSON]
                                                                                                                                                          (LockableFeature
                                                                                                                                                             SndFactorPasswordChallengeConfig))))))))))
                                                                                                                  :<|> Named
                                                                                                                         '("get-config",
                                                                                                                           MLSConfig)
                                                                                                                         (Summary
                                                                                                                            "[deprecated] Get feature config for feature mls"
                                                                                                                          :> (Until
                                                                                                                                'V2
                                                                                                                              :> (Description
                                                                                                                                    "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                                  :> (ZUser
                                                                                                                                      :> (CanThrow
                                                                                                                                            'NotATeamMember
                                                                                                                                          :> (CanThrow
                                                                                                                                                OperationDenied
                                                                                                                                              :> (CanThrow
                                                                                                                                                    'TeamNotFound
                                                                                                                                                  :> ("feature-configs"
                                                                                                                                                      :> ("mls"
                                                                                                                                                          :> Get
                                                                                                                                                               '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> (ServerT
   (Named
      '("get", MlsMigrationConfig)
      (Description (FeatureAPIDesc MlsMigrationConfig)
       :> (ZUser
           :> (Summary
                 (AppendSymbol "Get config for " (FeatureSymbol MlsMigrationConfig))
               :> (CanThrow OperationDenied
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> (FeatureSymbol MlsMigrationConfig
                                           :> Get
                                                '[JSON]
                                                (LockableFeature MlsMigrationConfig)))))))))))
    :<|> Named
           '("put", MlsMigrationConfig)
           (Description (FeatureAPIDesc MlsMigrationConfig)
            :> (ZUser
                :> (Summary
                      (AppendSymbol "Put config for " (FeatureSymbol MlsMigrationConfig))
                    :> (CanThrow OperationDenied
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany (FeatureErrors MlsMigrationConfig)
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> (FeatureSymbol MlsMigrationConfig
                                                        :> (ReqBody
                                                              '[JSON] (Feature MlsMigrationConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    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])
 -> ServerT
      (Named
         '("get", MlsMigrationConfig)
         (From 'V5
          :> (Description ""
              :> (ZUser
                  :> (Summary "Get config for mlsMigration"
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("mlsMigration"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature
                                                          MlsMigrationConfig))))))))))))
       :<|> Named
              '("put", MlsMigrationConfig)
              (From 'V5
               :> (Description ""
                   :> (ZUser
                       :> (Summary "Put config for mlsMigration"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("mlsMigration"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     (Feature MlsMigrationConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           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]))
-> API
     (Named
        '("get", MlsMigrationConfig)
        (Description (FeatureAPIDesc MlsMigrationConfig)
         :> (ZUser
             :> (Summary
                   (AppendSymbol "Get config for " (FeatureSymbol MlsMigrationConfig))
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> (FeatureSymbol MlsMigrationConfig
                                             :> Get
                                                  '[JSON]
                                                  (LockableFeature MlsMigrationConfig)))))))))))
      :<|> Named
             '("put", MlsMigrationConfig)
             (Description (FeatureAPIDesc MlsMigrationConfig)
              :> (ZUser
                  :> (Summary
                        (AppendSymbol "Put config for " (FeatureSymbol MlsMigrationConfig))
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> (CanThrow TeamFeatureError
                                      :> (CanThrowMany (FeatureErrors MlsMigrationConfig)
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> (FeatureSymbol MlsMigrationConfig
                                                          :> (ReqBody
                                                                '[JSON] (Feature MlsMigrationConfig)
                                                              :> Put
                                                                   '[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
        '("get", MlsMigrationConfig)
        (From 'V5
         :> (Description ""
             :> (ZUser
                 :> (Summary "Get config for mlsMigration"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("mlsMigration"
                                                 :> Get
                                                      '[JSON]
                                                      (LockableFeature
                                                         MlsMigrationConfig))))))))))))
      :<|> Named
             '("put", MlsMigrationConfig)
             (From 'V5
              :> (Description ""
                  :> (ZUser
                      :> (Summary "Put config for mlsMigration"
                          :> (CanThrow OperationDenied
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mlsMigration"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature MlsMigrationConfig)
                                                                  :> Put
                                                                       '[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 {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
  (Named
     '("get", MlsMigrationConfig)
     (Description (FeatureAPIDesc MlsMigrationConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol "Get config for " (FeatureSymbol MlsMigrationConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol MlsMigrationConfig
                                          :> Get
                                               '[JSON]
                                               (LockableFeature MlsMigrationConfig)))))))))))
   :<|> Named
          '("put", MlsMigrationConfig)
          (Description (FeatureAPIDesc MlsMigrationConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol "Put config for " (FeatureSymbol MlsMigrationConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors MlsMigrationConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol MlsMigrationConfig
                                                       :> (ReqBody
                                                             '[JSON] (Feature MlsMigrationConfig)
                                                           :> Put
                                                                '[JSON]
                                                                (LockableFeature
                                                                   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])
-> ServerT
     (Named
        '("get", MlsMigrationConfig)
        (Description (FeatureAPIDesc MlsMigrationConfig)
         :> (ZUser
             :> (Summary
                   (AppendSymbol "Get config for " (FeatureSymbol MlsMigrationConfig))
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> (FeatureSymbol MlsMigrationConfig
                                             :> Get
                                                  '[JSON]
                                                  (LockableFeature MlsMigrationConfig)))))))))))
      :<|> Named
             '("put", MlsMigrationConfig)
             (Description (FeatureAPIDesc MlsMigrationConfig)
              :> (ZUser
                  :> (Summary
                        (AppendSymbol "Put config for " (FeatureSymbol MlsMigrationConfig))
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> (CanThrow TeamFeatureError
                                      :> (CanThrowMany (FeatureErrors MlsMigrationConfig)
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> (FeatureSymbol MlsMigrationConfig
                                                          :> (ReqBody
                                                                '[JSON] (Feature MlsMigrationConfig)
                                                              :> Put
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      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])
ServerT
  (Named
     '("get", MlsMigrationConfig)
     (Description (FeatureAPIDesc MlsMigrationConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol "Get config for " (FeatureSymbol MlsMigrationConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol MlsMigrationConfig
                                          :> Get
                                               '[JSON]
                                               (LockableFeature MlsMigrationConfig)))))))))))
   :<|> Named
          '("put", MlsMigrationConfig)
          (Description (FeatureAPIDesc MlsMigrationConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol "Put config for " (FeatureSymbol MlsMigrationConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors MlsMigrationConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol MlsMigrationConfig
                                                       :> (ReqBody
                                                             '[JSON] (Feature MlsMigrationConfig)
                                                           :> Put
                                                                '[JSON]
                                                                (LockableFeature
                                                                   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])
-> ServerT
     (Named
        '("get", MlsMigrationConfig)
        (From 'V5
         :> (Description ""
             :> (ZUser
                 :> (Summary "Get config for mlsMigration"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("mlsMigration"
                                                 :> Get
                                                      '[JSON]
                                                      (LockableFeature
                                                         MlsMigrationConfig))))))))))))
      :<|> Named
             '("put", MlsMigrationConfig)
             (From 'V5
              :> (Description ""
                  :> (ZUser
                      :> (Summary "Put config for mlsMigration"
                          :> (CanThrow OperationDenied
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("mlsMigration"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature MlsMigrationConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          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])
forall a. a -> a
id API
  (Named
     '("get", MlsMigrationConfig)
     (Description (FeatureAPIDesc MlsMigrationConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol "Get config for " (FeatureSymbol MlsMigrationConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol MlsMigrationConfig
                                          :> Get
                                               '[JSON]
                                               (LockableFeature MlsMigrationConfig)))))))))))
   :<|> Named
          '("put", MlsMigrationConfig)
          (Description (FeatureAPIDesc MlsMigrationConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol "Put config for " (FeatureSymbol MlsMigrationConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany (FeatureErrors MlsMigrationConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol MlsMigrationConfig
                                                       :> (ReqBody
                                                             '[JSON] (Feature MlsMigrationConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", MlsMigrationConfig)
     (From 'V5
      :> (Description ""
          :> (ZUser
              :> (Summary "Get config for mlsMigration"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("mlsMigration"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature MlsMigrationConfig))))))))))))
   :<|> Named
          '("put", MlsMigrationConfig)
          (From 'V5
           :> (Description ""
               :> (ZUser
                   :> (Summary "Put config for mlsMigration"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("mlsMigration"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature MlsMigrationConfig)
                                                               :> Put
                                                                    '[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
         '("get", EnforceFileDownloadLocationConfig)
         (From 'V5
          :> (Description
                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
              :> (ZUser
                  :> (Summary "Get config for enforceFileDownloadLocation"
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("enforceFileDownloadLocation"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature
                                                          EnforceFileDownloadLocationConfig))))))))))))
       :<|> Named
              '("put", EnforceFileDownloadLocationConfig)
              (From 'V5
               :> (Description
                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                   :> (ZUser
                       :> (Summary "Put config for enforceFileDownloadLocation"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("enforceFileDownloadLocation"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     (Feature
                                                                        EnforceFileDownloadLocationConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           EnforceFileDownloadLocationConfig))))))))))))))))
      :<|> (Named
              '("get", LimitedEventFanoutConfig)
              (From 'V5
               :> (Description ""
                   :> (ZUser
                       :> (Summary "Get config for limitedEventFanout"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("limitedEventFanout"
                                                       :> Get
                                                            '[JSON]
                                                            (LockableFeature
                                                               LimitedEventFanoutConfig))))))))))))
            :<|> (Named
                    "get-all-feature-configs-for-user"
                    (Summary "Gets feature configs for a user"
                     :> (Description
                           "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                         :> (DescriptionOAuthScope 'ReadFeatureConfigs
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> Get '[JSON] AllTeamFeatures))))))))
                  :<|> (Named
                          "get-all-feature-configs-for-team"
                          (Summary "Gets feature configs for a team"
                           :> (Description
                                 "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'TeamNotFound
                                           :> (ZLocalUser
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> Get '[JSON] AllTeamFeatures)))))))))
                        :<|> ((Named
                                 '("get-deprecated", SearchVisibilityAvailableConfig)
                                 (ZUser
                                  :> (Summary "[deprecated] Get config for searchVisibility"
                                      :> (Until 'V2
                                          :> (Description
                                                "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow OperationDenied
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("search-visibility"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SearchVisibilityAvailableConfig))))))))))))
                               :<|> (Named
                                       '("put-deprecated", SearchVisibilityAvailableConfig)
                                       (ZUser
                                        :> (Summary "[deprecated] Get config for searchVisibility"
                                            :> (Until 'V2
                                                :> (Description
                                                      "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow OperationDenied
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("search-visibility"
                                                                                    :> (ReqBody
                                                                                          '[JSON]
                                                                                          (Feature
                                                                                             SearchVisibilityAvailableConfig)
                                                                                        :> Put
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                SearchVisibilityAvailableConfig))))))))))))))
                                     :<|> (Named
                                             '("get-deprecated", ValidateSAMLEmailsConfig)
                                             (ZUser
                                              :> (Summary
                                                    "[deprecated] Get config for validateSAMLemails"
                                                  :> (Until 'V2
                                                      :> (Description
                                                            "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow OperationDenied
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("validate-saml-emails"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              ValidateSAMLEmailsConfig))))))))))))
                                           :<|> Named
                                                  '("get-deprecated", DigitalSignaturesConfig)
                                                  (ZUser
                                                   :> (Summary
                                                         "[deprecated] Get config for digitalSignatures"
                                                       :> (Until 'V2
                                                           :> (Description
                                                                 "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("digital-signatures"
                                                                                           :> Get
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   DigitalSignaturesConfig)))))))))))))))
                              :<|> (Named
                                      '("get-config", LegalholdConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature legalhold"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("legalhold"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               LegalholdConfig))))))))))
                                    :<|> (Named
                                            '("get-config", SSOConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature sso"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("sso"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SSOConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", SearchVisibilityAvailableConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature searchVisibility"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("searchVisibility"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           SearchVisibilityAvailableConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", ValidateSAMLEmailsConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature validateSAMLemails"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("validateSAMLemails"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 ValidateSAMLEmailsConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                DigitalSignaturesConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature digitalSignatures"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("digitalSignatures"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       DigitalSignaturesConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config", AppLockConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature appLock"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("appLock"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             AppLockConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            FileSharingConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature fileSharing"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("fileSharing"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   FileSharingConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  ClassifiedDomainsConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature classifiedDomains"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("classifiedDomains"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         ClassifiedDomainsConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        ConferenceCallingConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature conferenceCalling"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("conferenceCalling"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               ConferenceCallingConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              SelfDeletingMessagesConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("selfDeletingMessages"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     SelfDeletingMessagesConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    GuestLinksConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           GuestLinksConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 SndFactorPasswordChallengeConfig))))))))))
                                                                                                      :<|> Named
                                                                                                             '("get-config",
                                                                                                               MLSConfig)
                                                                                                             (Summary
                                                                                                                "[deprecated] Get feature config for feature mls"
                                                                                                              :> (Until
                                                                                                                    'V2
                                                                                                                  :> (Description
                                                                                                                        "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                      :> (ZUser
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    OperationDenied
                                                                                                                                  :> (CanThrow
                                                                                                                                        'TeamNotFound
                                                                                                                                      :> ("feature-configs"
                                                                                                                                          :> ("mls"
                                                                                                                                              :> Get
                                                                                                                                                   '[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
         '("get", MlsMigrationConfig)
         (From 'V5
          :> (Description ""
              :> (ZUser
                  :> (Summary "Get config for mlsMigration"
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("mlsMigration"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature
                                                          MlsMigrationConfig))))))))))))
       :<|> Named
              '("put", MlsMigrationConfig)
              (From 'V5
               :> (Description ""
                   :> (ZUser
                       :> (Summary "Put config for mlsMigration"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("mlsMigration"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     (Feature MlsMigrationConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           MlsMigrationConfig))))))))))))))))
      :<|> ((Named
               '("get", EnforceFileDownloadLocationConfig)
               (From 'V5
                :> (Description
                      "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                    :> (ZUser
                        :> (Summary "Get config for enforceFileDownloadLocation"
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("enforceFileDownloadLocation"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature
                                                                EnforceFileDownloadLocationConfig))))))))))))
             :<|> Named
                    '("put", EnforceFileDownloadLocationConfig)
                    (From 'V5
                     :> (Description
                           "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                         :> (ZUser
                             :> (Summary "Put config for enforceFileDownloadLocation"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> (CanThrow TeamFeatureError
                                                 :> (CanThrowMany '[]
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> ("enforceFileDownloadLocation"
                                                                     :> (ReqBody
                                                                           '[JSON]
                                                                           (Feature
                                                                              EnforceFileDownloadLocationConfig)
                                                                         :> Put
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 EnforceFileDownloadLocationConfig))))))))))))))))
            :<|> (Named
                    '("get", LimitedEventFanoutConfig)
                    (From 'V5
                     :> (Description ""
                         :> (ZUser
                             :> (Summary "Get config for limitedEventFanout"
                                 :> (CanThrow OperationDenied
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("limitedEventFanout"
                                                             :> Get
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     LimitedEventFanoutConfig))))))))))))
                  :<|> (Named
                          "get-all-feature-configs-for-user"
                          (Summary "Gets feature configs for a user"
                           :> (Description
                                 "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                               :> (DescriptionOAuthScope 'ReadFeatureConfigs
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> Get '[JSON] AllTeamFeatures))))))))
                        :<|> (Named
                                "get-all-feature-configs-for-team"
                                (Summary "Gets feature configs for a team"
                                 :> (Description
                                       "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                                     :> (CanThrow 'NotATeamMember
                                         :> (CanThrow OperationDenied
                                             :> (CanThrow 'TeamNotFound
                                                 :> (ZLocalUser
                                                     :> ("teams"
                                                         :> (Capture "tid" TeamId
                                                             :> ("features"
                                                                 :> Get
                                                                      '[JSON]
                                                                      AllTeamFeatures)))))))))
                              :<|> ((Named
                                       '("get-deprecated", SearchVisibilityAvailableConfig)
                                       (ZUser
                                        :> (Summary "[deprecated] Get config for searchVisibility"
                                            :> (Until 'V2
                                                :> (Description
                                                      "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow OperationDenied
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("search-visibility"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        SearchVisibilityAvailableConfig))))))))))))
                                     :<|> (Named
                                             '("put-deprecated", SearchVisibilityAvailableConfig)
                                             (ZUser
                                              :> (Summary
                                                    "[deprecated] Get config for searchVisibility"
                                                  :> (Until 'V2
                                                      :> (Description
                                                            "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow OperationDenied
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> (CanThrow TeamFeatureError
                                                                          :> ("teams"
                                                                              :> (Capture
                                                                                    "tid" TeamId
                                                                                  :> ("features"
                                                                                      :> ("search-visibility"
                                                                                          :> (ReqBody
                                                                                                '[JSON]
                                                                                                (Feature
                                                                                                   SearchVisibilityAvailableConfig)
                                                                                              :> Put
                                                                                                   '[JSON]
                                                                                                   (LockableFeature
                                                                                                      SearchVisibilityAvailableConfig))))))))))))))
                                           :<|> (Named
                                                   '("get-deprecated", ValidateSAMLEmailsConfig)
                                                   (ZUser
                                                    :> (Summary
                                                          "[deprecated] Get config for validateSAMLemails"
                                                        :> (Until 'V2
                                                            :> (Description
                                                                  "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                                :> (CanThrow 'NotATeamMember
                                                                    :> (CanThrow OperationDenied
                                                                        :> (CanThrow 'TeamNotFound
                                                                            :> ("teams"
                                                                                :> (Capture
                                                                                      "tid" TeamId
                                                                                    :> ("features"
                                                                                        :> ("validate-saml-emails"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    ValidateSAMLEmailsConfig))))))))))))
                                                 :<|> Named
                                                        '("get-deprecated", DigitalSignaturesConfig)
                                                        (ZUser
                                                         :> (Summary
                                                               "[deprecated] Get config for digitalSignatures"
                                                             :> (Until 'V2
                                                                 :> (Description
                                                                       "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("teams"
                                                                                     :> (Capture
                                                                                           "tid"
                                                                                           TeamId
                                                                                         :> ("features"
                                                                                             :> ("digital-signatures"
                                                                                                 :> Get
                                                                                                      '[JSON]
                                                                                                      (LockableFeature
                                                                                                         DigitalSignaturesConfig)))))))))))))))
                                    :<|> (Named
                                            '("get-config", LegalholdConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature legalhold"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("legalhold"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     LegalholdConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", SSOConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature sso"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("sso"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           SSOConfig))))))))))
                                                :<|> (Named
                                                        '("get-config",
                                                          SearchVisibilityAvailableConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature searchVisibility"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("searchVisibility"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 SearchVisibilityAvailableConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                ValidateSAMLEmailsConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature validateSAMLemails"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("validateSAMLemails"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       ValidateSAMLEmailsConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      DigitalSignaturesConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature digitalSignatures"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("digitalSignatures"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             DigitalSignaturesConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            AppLockConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature appLock"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("appLock"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   AppLockConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  FileSharingConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature fileSharing"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("fileSharing"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         FileSharingConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        ClassifiedDomainsConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature classifiedDomains"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("classifiedDomains"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               ClassifiedDomainsConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              ConferenceCallingConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature conferenceCalling"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("conferenceCalling"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     ConferenceCallingConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    SelfDeletingMessagesConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("selfDeletingMessages"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           SelfDeletingMessagesConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          GuestLinksConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("conversationGuestLinks"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 GuestLinksConfig))))))))))
                                                                                                      :<|> (Named
                                                                                                              '("get-config",
                                                                                                                SndFactorPasswordChallengeConfig)
                                                                                                              (Summary
                                                                                                                 "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                               :> (Until
                                                                                                                     'V2
                                                                                                                   :> (Description
                                                                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                       :> (ZUser
                                                                                                                           :> (CanThrow
                                                                                                                                 'NotATeamMember
                                                                                                                               :> (CanThrow
                                                                                                                                     OperationDenied
                                                                                                                                   :> (CanThrow
                                                                                                                                         'TeamNotFound
                                                                                                                                       :> ("feature-configs"
                                                                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                                                                               :> Get
                                                                                                                                                    '[JSON]
                                                                                                                                                    (LockableFeature
                                                                                                                                                       SndFactorPasswordChallengeConfig))))))))))
                                                                                                            :<|> Named
                                                                                                                   '("get-config",
                                                                                                                     MLSConfig)
                                                                                                                   (Summary
                                                                                                                      "[deprecated] Get feature config for feature mls"
                                                                                                                    :> (Until
                                                                                                                          'V2
                                                                                                                        :> (Description
                                                                                                                              "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                            :> (ZUser
                                                                                                                                :> (CanThrow
                                                                                                                                      'NotATeamMember
                                                                                                                                    :> (CanThrow
                                                                                                                                          OperationDenied
                                                                                                                                        :> (CanThrow
                                                                                                                                              'TeamNotFound
                                                                                                                                            :> ("feature-configs"
                                                                                                                                                :> ("mls"
                                                                                                                                                    :> Get
                                                                                                                                                         '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> (ServerT
   (Named
      '("get", EnforceFileDownloadLocationConfig)
      (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
       :> (ZUser
           :> (Summary
                 (AppendSymbol
                    "Get config for "
                    (FeatureSymbol EnforceFileDownloadLocationConfig))
               :> (CanThrow OperationDenied
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> (FeatureSymbol EnforceFileDownloadLocationConfig
                                           :> Get
                                                '[JSON]
                                                (LockableFeature
                                                   EnforceFileDownloadLocationConfig)))))))))))
    :<|> Named
           '("put", EnforceFileDownloadLocationConfig)
           (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
            :> (ZUser
                :> (Summary
                      (AppendSymbol
                         "Put config for "
                         (FeatureSymbol EnforceFileDownloadLocationConfig))
                    :> (CanThrow OperationDenied
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow 'TeamNotFound
                                :> (CanThrow TeamFeatureError
                                    :> (CanThrowMany
                                          (FeatureErrors EnforceFileDownloadLocationConfig)
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> (FeatureSymbol
                                                          EnforceFileDownloadLocationConfig
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 EnforceFileDownloadLocationConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    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])
 -> ServerT
      (Named
         '("get", EnforceFileDownloadLocationConfig)
         (From 'V5
          :> (Description
                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
              :> (ZUser
                  :> (Summary "Get config for enforceFileDownloadLocation"
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("enforceFileDownloadLocation"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature
                                                          EnforceFileDownloadLocationConfig))))))))))))
       :<|> Named
              '("put", EnforceFileDownloadLocationConfig)
              (From 'V5
               :> (Description
                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                   :> (ZUser
                       :> (Summary "Put config for enforceFileDownloadLocation"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("enforceFileDownloadLocation"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     (Feature
                                                                        EnforceFileDownloadLocationConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           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]))
-> API
     (Named
        '("get", EnforceFileDownloadLocationConfig)
        (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
         :> (ZUser
             :> (Summary
                   (AppendSymbol
                      "Get config for "
                      (FeatureSymbol EnforceFileDownloadLocationConfig))
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> (FeatureSymbol EnforceFileDownloadLocationConfig
                                             :> Get
                                                  '[JSON]
                                                  (LockableFeature
                                                     EnforceFileDownloadLocationConfig)))))))))))
      :<|> Named
             '("put", EnforceFileDownloadLocationConfig)
             (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
              :> (ZUser
                  :> (Summary
                        (AppendSymbol
                           "Put config for "
                           (FeatureSymbol EnforceFileDownloadLocationConfig))
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> (CanThrow TeamFeatureError
                                      :> (CanThrowMany
                                            (FeatureErrors EnforceFileDownloadLocationConfig)
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> (FeatureSymbol
                                                            EnforceFileDownloadLocationConfig
                                                          :> (ReqBody
                                                                '[JSON]
                                                                (Feature
                                                                   EnforceFileDownloadLocationConfig)
                                                              :> Put
                                                                   '[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
        '("get", EnforceFileDownloadLocationConfig)
        (From 'V5
         :> (Description
               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
             :> (ZUser
                 :> (Summary "Get config for enforceFileDownloadLocation"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("enforceFileDownloadLocation"
                                                 :> Get
                                                      '[JSON]
                                                      (LockableFeature
                                                         EnforceFileDownloadLocationConfig))))))))))))
      :<|> Named
             '("put", EnforceFileDownloadLocationConfig)
             (From 'V5
              :> (Description
                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                  :> (ZUser
                      :> (Summary "Put config for enforceFileDownloadLocation"
                          :> (CanThrow OperationDenied
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("enforceFileDownloadLocation"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       EnforceFileDownloadLocationConfig)
                                                                  :> Put
                                                                       '[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 {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
  (Named
     '("get", EnforceFileDownloadLocationConfig)
     (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol
                   "Get config for "
                   (FeatureSymbol EnforceFileDownloadLocationConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol EnforceFileDownloadLocationConfig
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  EnforceFileDownloadLocationConfig)))))))))))
   :<|> Named
          '("put", EnforceFileDownloadLocationConfig)
          (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol
                        "Put config for "
                        (FeatureSymbol EnforceFileDownloadLocationConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany
                                         (FeatureErrors EnforceFileDownloadLocationConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol
                                                         EnforceFileDownloadLocationConfig
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature
                                                                EnforceFileDownloadLocationConfig)
                                                           :> Put
                                                                '[JSON]
                                                                (LockableFeature
                                                                   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])
-> ServerT
     (Named
        '("get", EnforceFileDownloadLocationConfig)
        (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
         :> (ZUser
             :> (Summary
                   (AppendSymbol
                      "Get config for "
                      (FeatureSymbol EnforceFileDownloadLocationConfig))
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow 'TeamNotFound
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features"
                                         :> (FeatureSymbol EnforceFileDownloadLocationConfig
                                             :> Get
                                                  '[JSON]
                                                  (LockableFeature
                                                     EnforceFileDownloadLocationConfig)))))))))))
      :<|> Named
             '("put", EnforceFileDownloadLocationConfig)
             (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
              :> (ZUser
                  :> (Summary
                        (AppendSymbol
                           "Put config for "
                           (FeatureSymbol EnforceFileDownloadLocationConfig))
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> (CanThrow TeamFeatureError
                                      :> (CanThrowMany
                                            (FeatureErrors EnforceFileDownloadLocationConfig)
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> (FeatureSymbol
                                                            EnforceFileDownloadLocationConfig
                                                          :> (ReqBody
                                                                '[JSON]
                                                                (Feature
                                                                   EnforceFileDownloadLocationConfig)
                                                              :> Put
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      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])
ServerT
  (Named
     '("get", EnforceFileDownloadLocationConfig)
     (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol
                   "Get config for "
                   (FeatureSymbol EnforceFileDownloadLocationConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol EnforceFileDownloadLocationConfig
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  EnforceFileDownloadLocationConfig)))))))))))
   :<|> Named
          '("put", EnforceFileDownloadLocationConfig)
          (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol
                        "Put config for "
                        (FeatureSymbol EnforceFileDownloadLocationConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany
                                         (FeatureErrors EnforceFileDownloadLocationConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol
                                                         EnforceFileDownloadLocationConfig
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature
                                                                EnforceFileDownloadLocationConfig)
                                                           :> Put
                                                                '[JSON]
                                                                (LockableFeature
                                                                   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])
-> ServerT
     (Named
        '("get", EnforceFileDownloadLocationConfig)
        (From 'V5
         :> (Description
               "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
             :> (ZUser
                 :> (Summary "Get config for enforceFileDownloadLocation"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("enforceFileDownloadLocation"
                                                 :> Get
                                                      '[JSON]
                                                      (LockableFeature
                                                         EnforceFileDownloadLocationConfig))))))))))))
      :<|> Named
             '("put", EnforceFileDownloadLocationConfig)
             (From 'V5
              :> (Description
                    "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                  :> (ZUser
                      :> (Summary "Put config for enforceFileDownloadLocation"
                          :> (CanThrow OperationDenied
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow 'TeamNotFound
                                      :> (CanThrow TeamFeatureError
                                          :> (CanThrowMany '[]
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("enforceFileDownloadLocation"
                                                              :> (ReqBody
                                                                    '[JSON]
                                                                    (Feature
                                                                       EnforceFileDownloadLocationConfig)
                                                                  :> Put
                                                                       '[JSON]
                                                                       (LockableFeature
                                                                          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])
forall a. a -> a
id API
  (Named
     '("get", EnforceFileDownloadLocationConfig)
     (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
      :> (ZUser
          :> (Summary
                (AppendSymbol
                   "Get config for "
                   (FeatureSymbol EnforceFileDownloadLocationConfig))
              :> (CanThrow OperationDenied
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow 'TeamNotFound
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features"
                                      :> (FeatureSymbol EnforceFileDownloadLocationConfig
                                          :> Get
                                               '[JSON]
                                               (LockableFeature
                                                  EnforceFileDownloadLocationConfig)))))))))))
   :<|> Named
          '("put", EnforceFileDownloadLocationConfig)
          (Description (FeatureAPIDesc EnforceFileDownloadLocationConfig)
           :> (ZUser
               :> (Summary
                     (AppendSymbol
                        "Put config for "
                        (FeatureSymbol EnforceFileDownloadLocationConfig))
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'NotATeamMember
                           :> (CanThrow 'TeamNotFound
                               :> (CanThrow TeamFeatureError
                                   :> (CanThrowMany
                                         (FeatureErrors EnforceFileDownloadLocationConfig)
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> (FeatureSymbol
                                                         EnforceFileDownloadLocationConfig
                                                       :> (ReqBody
                                                             '[JSON]
                                                             (Feature
                                                                EnforceFileDownloadLocationConfig)
                                                           :> Put
                                                                '[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 OperationDenied ())
      : Error (Tagged 'NotATeamMember ())
      : Error (Tagged 'TeamNotFound ()) : r),
 ComputeFeatureConstraints
   cfg
   (Error (Tagged OperationDenied ())
      : 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 OperationDenied ())
      : 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),
 ServerEffects
   (DeclaredErrorEffects
      (CanThrowMany (FeatureErrors cfg)
       :> ("teams"
           :> (Capture "tid" TeamId
               :> ("features"
                   :> (FeatureSymbol cfg
                       :> (ReqBody '[JSON] (Feature cfg)
                           :> Put '[JSON] (LockableFeature cfg))))))))
   r,
 SetFeatureConfig cfg, 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 (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
   (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 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 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
   NotificationSubsystem
   (Append
      (DeclaredErrorEffects
         (CanThrowMany (FeatureErrors cfg)
          :> ("teams"
              :> (Capture "tid" TeamId
                  :> ("features"
                      :> (FeatureSymbol cfg
                          :> (ReqBody '[JSON] (Feature cfg)
                              :> Put '[JSON] (LockableFeature cfg))))))))
      r)) =>
API (FeatureAPIGetPut cfg) r
featureAPIGetPut
    API
  (Named
     '("get", EnforceFileDownloadLocationConfig)
     (From 'V5
      :> (Description
            "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
          :> (ZUser
              :> (Summary "Get config for enforceFileDownloadLocation"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("enforceFileDownloadLocation"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      EnforceFileDownloadLocationConfig))))))))))))
   :<|> Named
          '("put", EnforceFileDownloadLocationConfig)
          (From 'V5
           :> (Description
                 "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
               :> (ZUser
                   :> (Summary "Put config for enforceFileDownloadLocation"
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow 'TeamNotFound
                                   :> (CanThrow TeamFeatureError
                                       :> (CanThrowMany '[]
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("enforceFileDownloadLocation"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    EnforceFileDownloadLocationConfig)
                                                               :> Put
                                                                    '[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
        '("get", LimitedEventFanoutConfig)
        (From 'V5
         :> (Description ""
             :> (ZUser
                 :> (Summary "Get config for limitedEventFanout"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("limitedEventFanout"
                                                 :> Get
                                                      '[JSON]
                                                      (LockableFeature
                                                         LimitedEventFanoutConfig))))))))))))
      :<|> (Named
              "get-all-feature-configs-for-user"
              (Summary "Gets feature configs for a user"
               :> (Description
                     "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                   :> (DescriptionOAuthScope 'ReadFeatureConfigs
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs" :> Get '[JSON] AllTeamFeatures))))))))
            :<|> (Named
                    "get-all-feature-configs-for-team"
                    (Summary "Gets feature configs for a team"
                     :> (Description
                           "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'TeamNotFound
                                     :> (ZLocalUser
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> Get '[JSON] AllTeamFeatures)))))))))
                  :<|> ((Named
                           '("get-deprecated", SearchVisibilityAvailableConfig)
                           (ZUser
                            :> (Summary "[deprecated] Get config for searchVisibility"
                                :> (Until 'V2
                                    :> (Description
                                          "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow OperationDenied
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("search-visibility"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            SearchVisibilityAvailableConfig))))))))))))
                         :<|> (Named
                                 '("put-deprecated", SearchVisibilityAvailableConfig)
                                 (ZUser
                                  :> (Summary "[deprecated] Get config for searchVisibility"
                                      :> (Until 'V2
                                          :> (Description
                                                "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow OperationDenied
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("search-visibility"
                                                                              :> (ReqBody
                                                                                    '[JSON]
                                                                                    (Feature
                                                                                       SearchVisibilityAvailableConfig)
                                                                                  :> Put
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          SearchVisibilityAvailableConfig))))))))))))))
                               :<|> (Named
                                       '("get-deprecated", ValidateSAMLEmailsConfig)
                                       (ZUser
                                        :> (Summary "[deprecated] Get config for validateSAMLemails"
                                            :> (Until 'V2
                                                :> (Description
                                                      "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow OperationDenied
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("validate-saml-emails"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        ValidateSAMLEmailsConfig))))))))))))
                                     :<|> Named
                                            '("get-deprecated", DigitalSignaturesConfig)
                                            (ZUser
                                             :> (Summary
                                                   "[deprecated] Get config for digitalSignatures"
                                                 :> (Until 'V2
                                                     :> (Description
                                                           "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("digital-signatures"
                                                                                     :> Get
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             DigitalSignaturesConfig)))))))))))))))
                        :<|> (Named
                                '("get-config", LegalholdConfig)
                                (Summary "[deprecated] Get feature config for feature legalhold"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("legalhold"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         LegalholdConfig))))))))))
                              :<|> (Named
                                      '("get-config", SSOConfig)
                                      (Summary "[deprecated] Get feature config for feature sso"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("sso"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SSOConfig))))))))))
                                    :<|> (Named
                                            '("get-config", SearchVisibilityAvailableConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature searchVisibility"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("searchVisibility"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SearchVisibilityAvailableConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", ValidateSAMLEmailsConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature validateSAMLemails"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("validateSAMLemails"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ValidateSAMLEmailsConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", DigitalSignaturesConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature digitalSignatures"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("digitalSignatures"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 DigitalSignaturesConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config", AppLockConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature appLock"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("appLock"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       AppLockConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      FileSharingConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature fileSharing"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("fileSharing"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             FileSharingConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            ClassifiedDomainsConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature classifiedDomains"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("classifiedDomains"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   ClassifiedDomainsConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  ConferenceCallingConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature conferenceCalling"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("conferenceCalling"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         ConferenceCallingConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        SelfDeletingMessagesConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("selfDeletingMessages"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               SelfDeletingMessagesConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              GuestLinksConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     GuestLinksConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           SndFactorPasswordChallengeConfig))))))))))
                                                                                                :<|> Named
                                                                                                       '("get-config",
                                                                                                         MLSConfig)
                                                                                                       (Summary
                                                                                                          "[deprecated] Get feature config for feature mls"
                                                                                                        :> (Until
                                                                                                              'V2
                                                                                                            :> (Description
                                                                                                                  "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                :> (ZUser
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              OperationDenied
                                                                                                                            :> (CanThrow
                                                                                                                                  'TeamNotFound
                                                                                                                                :> ("feature-configs"
                                                                                                                                    :> ("mls"
                                                                                                                                        :> Get
                                                                                                                                             '[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
         '("get", EnforceFileDownloadLocationConfig)
         (From 'V5
          :> (Description
                "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
              :> (ZUser
                  :> (Summary "Get config for enforceFileDownloadLocation"
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("enforceFileDownloadLocation"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature
                                                          EnforceFileDownloadLocationConfig))))))))))))
       :<|> Named
              '("put", EnforceFileDownloadLocationConfig)
              (From 'V5
               :> (Description
                     "<p><b>Custom feature: only supported on some dedicated on-prem systems.</b></p>"
                   :> (ZUser
                       :> (Summary "Put config for enforceFileDownloadLocation"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> (CanThrowMany '[]
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("enforceFileDownloadLocation"
                                                               :> (ReqBody
                                                                     '[JSON]
                                                                     (Feature
                                                                        EnforceFileDownloadLocationConfig)
                                                                   :> Put
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           EnforceFileDownloadLocationConfig))))))))))))))))
      :<|> (Named
              '("get", LimitedEventFanoutConfig)
              (From 'V5
               :> (Description ""
                   :> (ZUser
                       :> (Summary "Get config for limitedEventFanout"
                           :> (CanThrow OperationDenied
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("limitedEventFanout"
                                                       :> Get
                                                            '[JSON]
                                                            (LockableFeature
                                                               LimitedEventFanoutConfig))))))))))))
            :<|> (Named
                    "get-all-feature-configs-for-user"
                    (Summary "Gets feature configs for a user"
                     :> (Description
                           "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                         :> (DescriptionOAuthScope 'ReadFeatureConfigs
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> Get '[JSON] AllTeamFeatures))))))))
                  :<|> (Named
                          "get-all-feature-configs-for-team"
                          (Summary "Gets feature configs for a team"
                           :> (Description
                                 "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                               :> (CanThrow 'NotATeamMember
                                   :> (CanThrow OperationDenied
                                       :> (CanThrow 'TeamNotFound
                                           :> (ZLocalUser
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> Get '[JSON] AllTeamFeatures)))))))))
                        :<|> ((Named
                                 '("get-deprecated", SearchVisibilityAvailableConfig)
                                 (ZUser
                                  :> (Summary "[deprecated] Get config for searchVisibility"
                                      :> (Until 'V2
                                          :> (Description
                                                "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow OperationDenied
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("search-visibility"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  SearchVisibilityAvailableConfig))))))))))))
                               :<|> (Named
                                       '("put-deprecated", SearchVisibilityAvailableConfig)
                                       (ZUser
                                        :> (Summary "[deprecated] Get config for searchVisibility"
                                            :> (Until 'V2
                                                :> (Description
                                                      "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow OperationDenied
                                                            :> (CanThrow 'TeamNotFound
                                                                :> (CanThrow TeamFeatureError
                                                                    :> ("teams"
                                                                        :> (Capture "tid" TeamId
                                                                            :> ("features"
                                                                                :> ("search-visibility"
                                                                                    :> (ReqBody
                                                                                          '[JSON]
                                                                                          (Feature
                                                                                             SearchVisibilityAvailableConfig)
                                                                                        :> Put
                                                                                             '[JSON]
                                                                                             (LockableFeature
                                                                                                SearchVisibilityAvailableConfig))))))))))))))
                                     :<|> (Named
                                             '("get-deprecated", ValidateSAMLEmailsConfig)
                                             (ZUser
                                              :> (Summary
                                                    "[deprecated] Get config for validateSAMLemails"
                                                  :> (Until 'V2
                                                      :> (Description
                                                            "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                          :> (CanThrow 'NotATeamMember
                                                              :> (CanThrow OperationDenied
                                                                  :> (CanThrow 'TeamNotFound
                                                                      :> ("teams"
                                                                          :> (Capture "tid" TeamId
                                                                              :> ("features"
                                                                                  :> ("validate-saml-emails"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              ValidateSAMLEmailsConfig))))))))))))
                                           :<|> Named
                                                  '("get-deprecated", DigitalSignaturesConfig)
                                                  (ZUser
                                                   :> (Summary
                                                         "[deprecated] Get config for digitalSignatures"
                                                       :> (Until 'V2
                                                           :> (Description
                                                                 "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("teams"
                                                                               :> (Capture
                                                                                     "tid" TeamId
                                                                                   :> ("features"
                                                                                       :> ("digital-signatures"
                                                                                           :> Get
                                                                                                '[JSON]
                                                                                                (LockableFeature
                                                                                                   DigitalSignaturesConfig)))))))))))))))
                              :<|> (Named
                                      '("get-config", LegalholdConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature legalhold"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("legalhold"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               LegalholdConfig))))))))))
                                    :<|> (Named
                                            '("get-config", SSOConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature sso"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("sso"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SSOConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", SearchVisibilityAvailableConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature searchVisibility"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("searchVisibility"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           SearchVisibilityAvailableConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", ValidateSAMLEmailsConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature validateSAMLemails"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("validateSAMLemails"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 ValidateSAMLEmailsConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                DigitalSignaturesConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature digitalSignatures"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("digitalSignatures"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       DigitalSignaturesConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config", AppLockConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature appLock"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("appLock"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             AppLockConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            FileSharingConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature fileSharing"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("fileSharing"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   FileSharingConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  ClassifiedDomainsConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature classifiedDomains"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("classifiedDomains"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         ClassifiedDomainsConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        ConferenceCallingConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature conferenceCalling"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("conferenceCalling"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               ConferenceCallingConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              SelfDeletingMessagesConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("selfDeletingMessages"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     SelfDeletingMessagesConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    GuestLinksConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("conversationGuestLinks"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           GuestLinksConfig))))))))))
                                                                                                :<|> (Named
                                                                                                        '("get-config",
                                                                                                          SndFactorPasswordChallengeConfig)
                                                                                                        (Summary
                                                                                                           "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                         :> (Until
                                                                                                               'V2
                                                                                                             :> (Description
                                                                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                 :> (ZUser
                                                                                                                     :> (CanThrow
                                                                                                                           'NotATeamMember
                                                                                                                         :> (CanThrow
                                                                                                                               OperationDenied
                                                                                                                             :> (CanThrow
                                                                                                                                   'TeamNotFound
                                                                                                                                 :> ("feature-configs"
                                                                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                                                                         :> Get
                                                                                                                                              '[JSON]
                                                                                                                                              (LockableFeature
                                                                                                                                                 SndFactorPasswordChallengeConfig))))))))))
                                                                                                      :<|> Named
                                                                                                             '("get-config",
                                                                                                               MLSConfig)
                                                                                                             (Summary
                                                                                                                "[deprecated] Get feature config for feature mls"
                                                                                                              :> (Until
                                                                                                                    'V2
                                                                                                                  :> (Description
                                                                                                                        "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                      :> (ZUser
                                                                                                                          :> (CanThrow
                                                                                                                                'NotATeamMember
                                                                                                                              :> (CanThrow
                                                                                                                                    OperationDenied
                                                                                                                                  :> (CanThrow
                                                                                                                                        'TeamNotFound
                                                                                                                                      :> ("feature-configs"
                                                                                                                                          :> ("mls"
                                                                                                                                              :> Get
                                                                                                                                                   '[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 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", LimitedEventFanoutConfig) ServerT
  (From 'V5
   :> (Description ""
       :> (ZUser
           :> (Summary "Get config for limitedEventFanout"
               :> (CanThrow OperationDenied
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("limitedEventFanout"
                                           :> Get
                                                '[JSON]
                                                (LockableFeature
                                                   LimitedEventFanoutConfig))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (From 'V5
            :> (Description ""
                :> (ZUser
                    :> (Summary "Get config for limitedEventFanout"
                        :> (CanThrow OperationDenied
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("limitedEventFanout"
                                                    :> Get
                                                         '[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]))
UserId
-> TeamId
-> Sem
     '[Error (Tagged OperationDenied ()),
       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]
     (LockableFeature LimitedEventFanoutConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member TeamFeatureStore r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member TeamStore r) =>
UserId -> TeamId -> Sem r (LockableFeature cfg)
getFeature
    API
  (Named
     '("get", LimitedEventFanoutConfig)
     (From 'V5
      :> (Description ""
          :> (ZUser
              :> (Summary "Get config for limitedEventFanout"
                  :> (CanThrow OperationDenied
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("limitedEventFanout"
                                              :> Get
                                                   '[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
        "get-all-feature-configs-for-user"
        (Summary "Gets feature configs for a user"
         :> (Description
               "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
             :> (DescriptionOAuthScope 'ReadFeatureConfigs
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs" :> Get '[JSON] AllTeamFeatures))))))))
      :<|> (Named
              "get-all-feature-configs-for-team"
              (Summary "Gets feature configs for a team"
               :> (Description
                     "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'TeamNotFound
                               :> (ZLocalUser
                                   :> ("teams"
                                       :> (Capture "tid" TeamId
                                           :> ("features" :> Get '[JSON] AllTeamFeatures)))))))))
            :<|> ((Named
                     '("get-deprecated", SearchVisibilityAvailableConfig)
                     (ZUser
                      :> (Summary "[deprecated] Get config for searchVisibility"
                          :> (Until 'V2
                              :> (Description
                                    "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow OperationDenied
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("search-visibility"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      SearchVisibilityAvailableConfig))))))))))))
                   :<|> (Named
                           '("put-deprecated", SearchVisibilityAvailableConfig)
                           (ZUser
                            :> (Summary "[deprecated] Get config for searchVisibility"
                                :> (Until 'V2
                                    :> (Description
                                          "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow OperationDenied
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow TeamFeatureError
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("search-visibility"
                                                                        :> (ReqBody
                                                                              '[JSON]
                                                                              (Feature
                                                                                 SearchVisibilityAvailableConfig)
                                                                            :> Put
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    SearchVisibilityAvailableConfig))))))))))))))
                         :<|> (Named
                                 '("get-deprecated", ValidateSAMLEmailsConfig)
                                 (ZUser
                                  :> (Summary "[deprecated] Get config for validateSAMLemails"
                                      :> (Until 'V2
                                          :> (Description
                                                "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow OperationDenied
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("validate-saml-emails"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  ValidateSAMLEmailsConfig))))))))))))
                               :<|> Named
                                      '("get-deprecated", DigitalSignaturesConfig)
                                      (ZUser
                                       :> (Summary "[deprecated] Get config for digitalSignatures"
                                           :> (Until 'V2
                                               :> (Description
                                                     "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("digital-signatures"
                                                                               :> Get
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       DigitalSignaturesConfig)))))))))))))))
                  :<|> (Named
                          '("get-config", LegalholdConfig)
                          (Summary "[deprecated] Get feature config for feature legalhold"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("legalhold"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   LegalholdConfig))))))))))
                        :<|> (Named
                                '("get-config", SSOConfig)
                                (Summary "[deprecated] Get feature config for feature sso"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("sso"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SSOConfig))))))))))
                              :<|> (Named
                                      '("get-config", SearchVisibilityAvailableConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature searchVisibility"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("searchVisibility"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SearchVisibilityAvailableConfig))))))))))
                                    :<|> (Named
                                            '("get-config", ValidateSAMLEmailsConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature validateSAMLemails"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("validateSAMLemails"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ValidateSAMLEmailsConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", DigitalSignaturesConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature digitalSignatures"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("digitalSignatures"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           DigitalSignaturesConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", AppLockConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature appLock"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("appLock"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 AppLockConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config", FileSharingConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature fileSharing"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("fileSharing"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       FileSharingConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      ClassifiedDomainsConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature classifiedDomains"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("classifiedDomains"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             ClassifiedDomainsConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            ConferenceCallingConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature conferenceCalling"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("conferenceCalling"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   ConferenceCallingConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  SelfDeletingMessagesConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("selfDeletingMessages"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         SelfDeletingMessagesConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        GuestLinksConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               GuestLinksConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              SndFactorPasswordChallengeConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     SndFactorPasswordChallengeConfig))))))))))
                                                                                          :<|> Named
                                                                                                 '("get-config",
                                                                                                   MLSConfig)
                                                                                                 (Summary
                                                                                                    "[deprecated] Get feature config for feature mls"
                                                                                                  :> (Until
                                                                                                        'V2
                                                                                                      :> (Description
                                                                                                            "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                          :> (ZUser
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        OperationDenied
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> ("feature-configs"
                                                                                                                              :> ("mls"
                                                                                                                                  :> Get
                                                                                                                                       '[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
        '("get", LimitedEventFanoutConfig)
        (From 'V5
         :> (Description ""
             :> (ZUser
                 :> (Summary "Get config for limitedEventFanout"
                     :> (CanThrow OperationDenied
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("limitedEventFanout"
                                                 :> Get
                                                      '[JSON]
                                                      (LockableFeature
                                                         LimitedEventFanoutConfig))))))))))))
      :<|> (Named
              "get-all-feature-configs-for-user"
              (Summary "Gets feature configs for a user"
               :> (Description
                     "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                   :> (DescriptionOAuthScope 'ReadFeatureConfigs
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs" :> Get '[JSON] AllTeamFeatures))))))))
            :<|> (Named
                    "get-all-feature-configs-for-team"
                    (Summary "Gets feature configs for a team"
                     :> (Description
                           "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                         :> (CanThrow 'NotATeamMember
                             :> (CanThrow OperationDenied
                                 :> (CanThrow 'TeamNotFound
                                     :> (ZLocalUser
                                         :> ("teams"
                                             :> (Capture "tid" TeamId
                                                 :> ("features"
                                                     :> Get '[JSON] AllTeamFeatures)))))))))
                  :<|> ((Named
                           '("get-deprecated", SearchVisibilityAvailableConfig)
                           (ZUser
                            :> (Summary "[deprecated] Get config for searchVisibility"
                                :> (Until 'V2
                                    :> (Description
                                          "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow OperationDenied
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("search-visibility"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            SearchVisibilityAvailableConfig))))))))))))
                         :<|> (Named
                                 '("put-deprecated", SearchVisibilityAvailableConfig)
                                 (ZUser
                                  :> (Summary "[deprecated] Get config for searchVisibility"
                                      :> (Until 'V2
                                          :> (Description
                                                "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow OperationDenied
                                                      :> (CanThrow 'TeamNotFound
                                                          :> (CanThrow TeamFeatureError
                                                              :> ("teams"
                                                                  :> (Capture "tid" TeamId
                                                                      :> ("features"
                                                                          :> ("search-visibility"
                                                                              :> (ReqBody
                                                                                    '[JSON]
                                                                                    (Feature
                                                                                       SearchVisibilityAvailableConfig)
                                                                                  :> Put
                                                                                       '[JSON]
                                                                                       (LockableFeature
                                                                                          SearchVisibilityAvailableConfig))))))))))))))
                               :<|> (Named
                                       '("get-deprecated", ValidateSAMLEmailsConfig)
                                       (ZUser
                                        :> (Summary "[deprecated] Get config for validateSAMLemails"
                                            :> (Until 'V2
                                                :> (Description
                                                      "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                                    :> (CanThrow 'NotATeamMember
                                                        :> (CanThrow OperationDenied
                                                            :> (CanThrow 'TeamNotFound
                                                                :> ("teams"
                                                                    :> (Capture "tid" TeamId
                                                                        :> ("features"
                                                                            :> ("validate-saml-emails"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        ValidateSAMLEmailsConfig))))))))))))
                                     :<|> Named
                                            '("get-deprecated", DigitalSignaturesConfig)
                                            (ZUser
                                             :> (Summary
                                                   "[deprecated] Get config for digitalSignatures"
                                                 :> (Until 'V2
                                                     :> (Description
                                                           "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("teams"
                                                                         :> (Capture "tid" TeamId
                                                                             :> ("features"
                                                                                 :> ("digital-signatures"
                                                                                     :> Get
                                                                                          '[JSON]
                                                                                          (LockableFeature
                                                                                             DigitalSignaturesConfig)))))))))))))))
                        :<|> (Named
                                '("get-config", LegalholdConfig)
                                (Summary "[deprecated] Get feature config for feature legalhold"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("legalhold"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         LegalholdConfig))))))))))
                              :<|> (Named
                                      '("get-config", SSOConfig)
                                      (Summary "[deprecated] Get feature config for feature sso"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("sso"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SSOConfig))))))))))
                                    :<|> (Named
                                            '("get-config", SearchVisibilityAvailableConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature searchVisibility"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("searchVisibility"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SearchVisibilityAvailableConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", ValidateSAMLEmailsConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature validateSAMLemails"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("validateSAMLemails"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ValidateSAMLEmailsConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", DigitalSignaturesConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature digitalSignatures"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("digitalSignatures"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 DigitalSignaturesConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config", AppLockConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature appLock"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("appLock"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       AppLockConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      FileSharingConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature fileSharing"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("fileSharing"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             FileSharingConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            ClassifiedDomainsConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature classifiedDomains"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("classifiedDomains"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   ClassifiedDomainsConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  ConferenceCallingConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature conferenceCalling"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("conferenceCalling"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         ConferenceCallingConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        SelfDeletingMessagesConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("selfDeletingMessages"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               SelfDeletingMessagesConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              GuestLinksConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("conversationGuestLinks"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     GuestLinksConfig))))))))))
                                                                                          :<|> (Named
                                                                                                  '("get-config",
                                                                                                    SndFactorPasswordChallengeConfig)
                                                                                                  (Summary
                                                                                                     "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                                   :> (Until
                                                                                                         'V2
                                                                                                       :> (Description
                                                                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                           :> (ZUser
                                                                                                               :> (CanThrow
                                                                                                                     'NotATeamMember
                                                                                                                   :> (CanThrow
                                                                                                                         OperationDenied
                                                                                                                       :> (CanThrow
                                                                                                                             'TeamNotFound
                                                                                                                           :> ("feature-configs"
                                                                                                                               :> ("sndFactorPasswordChallenge"
                                                                                                                                   :> Get
                                                                                                                                        '[JSON]
                                                                                                                                        (LockableFeature
                                                                                                                                           SndFactorPasswordChallengeConfig))))))))))
                                                                                                :<|> Named
                                                                                                       '("get-config",
                                                                                                         MLSConfig)
                                                                                                       (Summary
                                                                                                          "[deprecated] Get feature config for feature mls"
                                                                                                        :> (Until
                                                                                                              'V2
                                                                                                            :> (Description
                                                                                                                  "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                                :> (ZUser
                                                                                                                    :> (CanThrow
                                                                                                                          'NotATeamMember
                                                                                                                        :> (CanThrow
                                                                                                                              OperationDenied
                                                                                                                            :> (CanThrow
                                                                                                                                  'TeamNotFound
                                                                                                                                :> ("feature-configs"
                                                                                                                                    :> ("mls"
                                                                                                                                        :> Get
                                                                                                                                             '[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 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-all-feature-configs-for-user" ServerT
  (Summary "Gets feature configs for a user"
   :> (Description
         "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
       :> (DescriptionOAuthScope 'ReadFeatureConfigs
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs" :> Get '[JSON] AllTeamFeatures))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Gets feature configs for a user"
            :> (Description
                  "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
                :> (DescriptionOAuthScope 'ReadFeatureConfigs
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs" :> 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]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     AllTeamFeatures
forall (r :: EffectRow).
(Member BrigAccess r, Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member (Input Opts) r, Member LegalHoldStore r,
 Member TeamFeatureStore r, Member TeamStore r) =>
UserId -> Sem r AllTeamFeatures
getAllTeamFeaturesForUser
    API
  (Named
     "get-all-feature-configs-for-user"
     (Summary "Gets feature configs for a user"
      :> (Description
            "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
          :> (DescriptionOAuthScope 'ReadFeatureConfigs
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs" :> 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
        "get-all-feature-configs-for-team"
        (Summary "Gets feature configs for a team"
         :> (Description
               "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'TeamNotFound
                         :> (ZLocalUser
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features" :> Get '[JSON] AllTeamFeatures)))))))))
      :<|> ((Named
               '("get-deprecated", SearchVisibilityAvailableConfig)
               (ZUser
                :> (Summary "[deprecated] Get config for searchVisibility"
                    :> (Until 'V2
                        :> (Description
                              "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow OperationDenied
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("search-visibility"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature
                                                                SearchVisibilityAvailableConfig))))))))))))
             :<|> (Named
                     '("put-deprecated", SearchVisibilityAvailableConfig)
                     (ZUser
                      :> (Summary "[deprecated] Get config for searchVisibility"
                          :> (Until 'V2
                              :> (Description
                                    "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow OperationDenied
                                          :> (CanThrow 'TeamNotFound
                                              :> (CanThrow TeamFeatureError
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("search-visibility"
                                                                  :> (ReqBody
                                                                        '[JSON]
                                                                        (Feature
                                                                           SearchVisibilityAvailableConfig)
                                                                      :> Put
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              SearchVisibilityAvailableConfig))))))))))))))
                   :<|> (Named
                           '("get-deprecated", ValidateSAMLEmailsConfig)
                           (ZUser
                            :> (Summary "[deprecated] Get config for validateSAMLemails"
                                :> (Until 'V2
                                    :> (Description
                                          "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow OperationDenied
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("validate-saml-emails"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            ValidateSAMLEmailsConfig))))))))))))
                         :<|> Named
                                '("get-deprecated", DigitalSignaturesConfig)
                                (ZUser
                                 :> (Summary "[deprecated] Get config for digitalSignatures"
                                     :> (Until 'V2
                                         :> (Description
                                               "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("digital-signatures"
                                                                         :> Get
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 DigitalSignaturesConfig)))))))))))))))
            :<|> (Named
                    '("get-config", LegalholdConfig)
                    (Summary "[deprecated] Get feature config for feature legalhold"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("legalhold"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature LegalholdConfig))))))))))
                  :<|> (Named
                          '("get-config", SSOConfig)
                          (Summary "[deprecated] Get feature config for feature sso"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("sso"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature SSOConfig))))))))))
                        :<|> (Named
                                '("get-config", SearchVisibilityAvailableConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature searchVisibility"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("searchVisibility"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SearchVisibilityAvailableConfig))))))))))
                              :<|> (Named
                                      '("get-config", ValidateSAMLEmailsConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature validateSAMLemails"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("validateSAMLemails"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ValidateSAMLEmailsConfig))))))))))
                                    :<|> (Named
                                            '("get-config", DigitalSignaturesConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature digitalSignatures"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("digitalSignatures"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     DigitalSignaturesConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", AppLockConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature appLock"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("appLock"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           AppLockConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", FileSharingConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature fileSharing"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("fileSharing"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 FileSharingConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                ClassifiedDomainsConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature classifiedDomains"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("classifiedDomains"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       ClassifiedDomainsConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      ConferenceCallingConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature conferenceCalling"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("conferenceCalling"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             ConferenceCallingConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            SelfDeletingMessagesConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("selfDeletingMessages"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   SelfDeletingMessagesConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  GuestLinksConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("conversationGuestLinks"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         GuestLinksConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        SndFactorPasswordChallengeConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               SndFactorPasswordChallengeConfig))))))))))
                                                                                    :<|> Named
                                                                                           '("get-config",
                                                                                             MLSConfig)
                                                                                           (Summary
                                                                                              "[deprecated] Get feature config for feature mls"
                                                                                            :> (Until
                                                                                                  'V2
                                                                                                :> (Description
                                                                                                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                    :> (ZUser
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  OperationDenied
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> ("feature-configs"
                                                                                                                        :> ("mls"
                                                                                                                            :> Get
                                                                                                                                 '[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
        "get-all-feature-configs-for-user"
        (Summary "Gets feature configs for a user"
         :> (Description
               "Gets feature configs for a user. If the user is a member of a team and has the required permissions, this will return the team's feature configs.If the user is not a member of a team, this will return the personal feature configs (the server defaults)."
             :> (DescriptionOAuthScope 'ReadFeatureConfigs
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs" :> Get '[JSON] AllTeamFeatures))))))))
      :<|> (Named
              "get-all-feature-configs-for-team"
              (Summary "Gets feature configs for a team"
               :> (Description
                     "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                   :> (CanThrow 'NotATeamMember
                       :> (CanThrow OperationDenied
                           :> (CanThrow 'TeamNotFound
                               :> (ZLocalUser
                                   :> ("teams"
                                       :> (Capture "tid" TeamId
                                           :> ("features" :> Get '[JSON] AllTeamFeatures)))))))))
            :<|> ((Named
                     '("get-deprecated", SearchVisibilityAvailableConfig)
                     (ZUser
                      :> (Summary "[deprecated] Get config for searchVisibility"
                          :> (Until 'V2
                              :> (Description
                                    "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow OperationDenied
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("search-visibility"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      SearchVisibilityAvailableConfig))))))))))))
                   :<|> (Named
                           '("put-deprecated", SearchVisibilityAvailableConfig)
                           (ZUser
                            :> (Summary "[deprecated] Get config for searchVisibility"
                                :> (Until 'V2
                                    :> (Description
                                          "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow OperationDenied
                                                :> (CanThrow 'TeamNotFound
                                                    :> (CanThrow TeamFeatureError
                                                        :> ("teams"
                                                            :> (Capture "tid" TeamId
                                                                :> ("features"
                                                                    :> ("search-visibility"
                                                                        :> (ReqBody
                                                                              '[JSON]
                                                                              (Feature
                                                                                 SearchVisibilityAvailableConfig)
                                                                            :> Put
                                                                                 '[JSON]
                                                                                 (LockableFeature
                                                                                    SearchVisibilityAvailableConfig))))))))))))))
                         :<|> (Named
                                 '("get-deprecated", ValidateSAMLEmailsConfig)
                                 (ZUser
                                  :> (Summary "[deprecated] Get config for validateSAMLemails"
                                      :> (Until 'V2
                                          :> (Description
                                                "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                              :> (CanThrow 'NotATeamMember
                                                  :> (CanThrow OperationDenied
                                                      :> (CanThrow 'TeamNotFound
                                                          :> ("teams"
                                                              :> (Capture "tid" TeamId
                                                                  :> ("features"
                                                                      :> ("validate-saml-emails"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  ValidateSAMLEmailsConfig))))))))))))
                               :<|> Named
                                      '("get-deprecated", DigitalSignaturesConfig)
                                      (ZUser
                                       :> (Summary "[deprecated] Get config for digitalSignatures"
                                           :> (Until 'V2
                                               :> (Description
                                                     "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("teams"
                                                                   :> (Capture "tid" TeamId
                                                                       :> ("features"
                                                                           :> ("digital-signatures"
                                                                               :> Get
                                                                                    '[JSON]
                                                                                    (LockableFeature
                                                                                       DigitalSignaturesConfig)))))))))))))))
                  :<|> (Named
                          '("get-config", LegalholdConfig)
                          (Summary "[deprecated] Get feature config for feature legalhold"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("legalhold"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   LegalholdConfig))))))))))
                        :<|> (Named
                                '("get-config", SSOConfig)
                                (Summary "[deprecated] Get feature config for feature sso"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("sso"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SSOConfig))))))))))
                              :<|> (Named
                                      '("get-config", SearchVisibilityAvailableConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature searchVisibility"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("searchVisibility"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SearchVisibilityAvailableConfig))))))))))
                                    :<|> (Named
                                            '("get-config", ValidateSAMLEmailsConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature validateSAMLemails"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("validateSAMLemails"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ValidateSAMLEmailsConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", DigitalSignaturesConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature digitalSignatures"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("digitalSignatures"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           DigitalSignaturesConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", AppLockConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature appLock"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("appLock"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 AppLockConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config", FileSharingConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature fileSharing"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("fileSharing"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       FileSharingConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      ClassifiedDomainsConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature classifiedDomains"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("classifiedDomains"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             ClassifiedDomainsConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            ConferenceCallingConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature conferenceCalling"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("conferenceCalling"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   ConferenceCallingConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  SelfDeletingMessagesConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("selfDeletingMessages"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         SelfDeletingMessagesConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        GuestLinksConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("conversationGuestLinks"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               GuestLinksConfig))))))))))
                                                                                    :<|> (Named
                                                                                            '("get-config",
                                                                                              SndFactorPasswordChallengeConfig)
                                                                                            (Summary
                                                                                               "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                             :> (Until
                                                                                                   'V2
                                                                                                 :> (Description
                                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                     :> (ZUser
                                                                                                         :> (CanThrow
                                                                                                               'NotATeamMember
                                                                                                             :> (CanThrow
                                                                                                                   OperationDenied
                                                                                                                 :> (CanThrow
                                                                                                                       'TeamNotFound
                                                                                                                     :> ("feature-configs"
                                                                                                                         :> ("sndFactorPasswordChallenge"
                                                                                                                             :> Get
                                                                                                                                  '[JSON]
                                                                                                                                  (LockableFeature
                                                                                                                                     SndFactorPasswordChallengeConfig))))))))))
                                                                                          :<|> Named
                                                                                                 '("get-config",
                                                                                                   MLSConfig)
                                                                                                 (Summary
                                                                                                    "[deprecated] Get feature config for feature mls"
                                                                                                  :> (Until
                                                                                                        'V2
                                                                                                      :> (Description
                                                                                                            "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                          :> (ZUser
                                                                                                              :> (CanThrow
                                                                                                                    'NotATeamMember
                                                                                                                  :> (CanThrow
                                                                                                                        OperationDenied
                                                                                                                      :> (CanThrow
                                                                                                                            'TeamNotFound
                                                                                                                          :> ("feature-configs"
                                                                                                                              :> ("mls"
                                                                                                                                  :> Get
                                                                                                                                       '[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 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-all-feature-configs-for-team" ServerT
  (Summary "Gets feature configs for a team"
   :> (Description
         "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
       :> (CanThrow 'NotATeamMember
           :> (CanThrow OperationDenied
               :> (CanThrow 'TeamNotFound
                   :> (ZLocalUser
                       :> ("teams"
                           :> (Capture "tid" TeamId
                               :> ("features" :> Get '[JSON] AllTeamFeatures)))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "Gets feature configs for a team"
            :> (Description
                  "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
                :> (CanThrow 'NotATeamMember
                    :> (CanThrow OperationDenied
                        :> (CanThrow 'TeamNotFound
                            :> (ZLocalUser
                                :> ("teams"
                                    :> (Capture "tid" TeamId
                                        :> ("features" :> 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]))
Local UserId
-> TeamId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     AllTeamFeatures
forall (r :: EffectRow).
(Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member LegalHoldStore r, Member TeamFeatureStore r,
 Member TeamStore r) =>
Local UserId -> TeamId -> Sem r AllTeamFeatures
getAllTeamFeaturesForTeam
    API
  (Named
     "get-all-feature-configs-for-team"
     (Summary "Gets feature configs for a team"
      :> (Description
            "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
          :> (CanThrow 'NotATeamMember
              :> (CanThrow OperationDenied
                  :> (CanThrow 'TeamNotFound
                      :> (ZLocalUser
                          :> ("teams"
                              :> (Capture "tid" TeamId
                                  :> ("features" :> 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
         '("get-deprecated", SearchVisibilityAvailableConfig)
         (ZUser
          :> (Summary "[deprecated] Get config for searchVisibility"
              :> (Until 'V2
                  :> (Description
                        "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow OperationDenied
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("search-visibility"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature
                                                          SearchVisibilityAvailableConfig))))))))))))
       :<|> (Named
               '("put-deprecated", SearchVisibilityAvailableConfig)
               (ZUser
                :> (Summary "[deprecated] Get config for searchVisibility"
                    :> (Until 'V2
                        :> (Description
                              "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow OperationDenied
                                    :> (CanThrow 'TeamNotFound
                                        :> (CanThrow TeamFeatureError
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("search-visibility"
                                                            :> (ReqBody
                                                                  '[JSON]
                                                                  (Feature
                                                                     SearchVisibilityAvailableConfig)
                                                                :> Put
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        SearchVisibilityAvailableConfig))))))))))))))
             :<|> (Named
                     '("get-deprecated", ValidateSAMLEmailsConfig)
                     (ZUser
                      :> (Summary "[deprecated] Get config for validateSAMLemails"
                          :> (Until 'V2
                              :> (Description
                                    "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow OperationDenied
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("validate-saml-emails"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      ValidateSAMLEmailsConfig))))))))))))
                   :<|> Named
                          '("get-deprecated", DigitalSignaturesConfig)
                          (ZUser
                           :> (Summary "[deprecated] Get config for digitalSignatures"
                               :> (Until 'V2
                                   :> (Description
                                         "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("digital-signatures"
                                                                   :> Get
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           DigitalSignaturesConfig)))))))))))))))
      :<|> (Named
              '("get-config", LegalholdConfig)
              (Summary "[deprecated] Get feature config for feature legalhold"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("legalhold"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature LegalholdConfig))))))))))
            :<|> (Named
                    '("get-config", SSOConfig)
                    (Summary "[deprecated] Get feature config for feature sso"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("sso"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature SSOConfig))))))))))
                  :<|> (Named
                          '("get-config", SearchVisibilityAvailableConfig)
                          (Summary
                             "[deprecated] Get feature config for feature searchVisibility"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("searchVisibility"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   SearchVisibilityAvailableConfig))))))))))
                        :<|> (Named
                                '("get-config", ValidateSAMLEmailsConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature validateSAMLemails"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("validateSAMLemails"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ValidateSAMLEmailsConfig))))))))))
                              :<|> (Named
                                      '("get-config", DigitalSignaturesConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature digitalSignatures"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("digitalSignatures"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               DigitalSignaturesConfig))))))))))
                                    :<|> (Named
                                            '("get-config", AppLockConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature appLock"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("appLock"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     AppLockConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", FileSharingConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature fileSharing"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("fileSharing"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           FileSharingConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", ClassifiedDomainsConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature classifiedDomains"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("classifiedDomains"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 ClassifiedDomainsConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                ConferenceCallingConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature conferenceCalling"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("conferenceCalling"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       ConferenceCallingConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      SelfDeletingMessagesConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("selfDeletingMessages"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             SelfDeletingMessagesConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            GuestLinksConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("conversationGuestLinks"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   GuestLinksConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  SndFactorPasswordChallengeConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         SndFactorPasswordChallengeConfig))))))))))
                                                                              :<|> Named
                                                                                     '("get-config",
                                                                                       MLSConfig)
                                                                                     (Summary
                                                                                        "[deprecated] Get feature config for feature mls"
                                                                                      :> (Until 'V2
                                                                                          :> (Description
                                                                                                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                              :> (ZUser
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            OperationDenied
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> ("feature-configs"
                                                                                                                  :> ("mls"
                                                                                                                      :> Get
                                                                                                                           '[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
        "get-all-feature-configs-for-team"
        (Summary "Gets feature configs for a team"
         :> (Description
               "Gets feature configs for a team. User must be a member of the team and have permission to view team features."
             :> (CanThrow 'NotATeamMember
                 :> (CanThrow OperationDenied
                     :> (CanThrow 'TeamNotFound
                         :> (ZLocalUser
                             :> ("teams"
                                 :> (Capture "tid" TeamId
                                     :> ("features" :> Get '[JSON] AllTeamFeatures)))))))))
      :<|> ((Named
               '("get-deprecated", SearchVisibilityAvailableConfig)
               (ZUser
                :> (Summary "[deprecated] Get config for searchVisibility"
                    :> (Until 'V2
                        :> (Description
                              "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow OperationDenied
                                    :> (CanThrow 'TeamNotFound
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("search-visibility"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature
                                                                SearchVisibilityAvailableConfig))))))))))))
             :<|> (Named
                     '("put-deprecated", SearchVisibilityAvailableConfig)
                     (ZUser
                      :> (Summary "[deprecated] Get config for searchVisibility"
                          :> (Until 'V2
                              :> (Description
                                    "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow OperationDenied
                                          :> (CanThrow 'TeamNotFound
                                              :> (CanThrow TeamFeatureError
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("search-visibility"
                                                                  :> (ReqBody
                                                                        '[JSON]
                                                                        (Feature
                                                                           SearchVisibilityAvailableConfig)
                                                                      :> Put
                                                                           '[JSON]
                                                                           (LockableFeature
                                                                              SearchVisibilityAvailableConfig))))))))))))))
                   :<|> (Named
                           '("get-deprecated", ValidateSAMLEmailsConfig)
                           (ZUser
                            :> (Summary "[deprecated] Get config for validateSAMLemails"
                                :> (Until 'V2
                                    :> (Description
                                          "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                        :> (CanThrow 'NotATeamMember
                                            :> (CanThrow OperationDenied
                                                :> (CanThrow 'TeamNotFound
                                                    :> ("teams"
                                                        :> (Capture "tid" TeamId
                                                            :> ("features"
                                                                :> ("validate-saml-emails"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            ValidateSAMLEmailsConfig))))))))))))
                         :<|> Named
                                '("get-deprecated", DigitalSignaturesConfig)
                                (ZUser
                                 :> (Summary "[deprecated] Get config for digitalSignatures"
                                     :> (Until 'V2
                                         :> (Description
                                               "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("teams"
                                                             :> (Capture "tid" TeamId
                                                                 :> ("features"
                                                                     :> ("digital-signatures"
                                                                         :> Get
                                                                              '[JSON]
                                                                              (LockableFeature
                                                                                 DigitalSignaturesConfig)))))))))))))))
            :<|> (Named
                    '("get-config", LegalholdConfig)
                    (Summary "[deprecated] Get feature config for feature legalhold"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("legalhold"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature LegalholdConfig))))))))))
                  :<|> (Named
                          '("get-config", SSOConfig)
                          (Summary "[deprecated] Get feature config for feature sso"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("sso"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature SSOConfig))))))))))
                        :<|> (Named
                                '("get-config", SearchVisibilityAvailableConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature searchVisibility"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("searchVisibility"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SearchVisibilityAvailableConfig))))))))))
                              :<|> (Named
                                      '("get-config", ValidateSAMLEmailsConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature validateSAMLemails"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("validateSAMLemails"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ValidateSAMLEmailsConfig))))))))))
                                    :<|> (Named
                                            '("get-config", DigitalSignaturesConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature digitalSignatures"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("digitalSignatures"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     DigitalSignaturesConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", AppLockConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature appLock"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("appLock"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           AppLockConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", FileSharingConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature fileSharing"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("fileSharing"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 FileSharingConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                ClassifiedDomainsConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature classifiedDomains"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("classifiedDomains"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       ClassifiedDomainsConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      ConferenceCallingConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature conferenceCalling"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("conferenceCalling"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             ConferenceCallingConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            SelfDeletingMessagesConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("selfDeletingMessages"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   SelfDeletingMessagesConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  GuestLinksConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("conversationGuestLinks"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         GuestLinksConfig))))))))))
                                                                              :<|> (Named
                                                                                      '("get-config",
                                                                                        SndFactorPasswordChallengeConfig)
                                                                                      (Summary
                                                                                         "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                       :> (Until 'V2
                                                                                           :> (Description
                                                                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                               :> (ZUser
                                                                                                   :> (CanThrow
                                                                                                         'NotATeamMember
                                                                                                       :> (CanThrow
                                                                                                             OperationDenied
                                                                                                           :> (CanThrow
                                                                                                                 'TeamNotFound
                                                                                                               :> ("feature-configs"
                                                                                                                   :> ("sndFactorPasswordChallenge"
                                                                                                                       :> Get
                                                                                                                            '[JSON]
                                                                                                                            (LockableFeature
                                                                                                                               SndFactorPasswordChallengeConfig))))))))))
                                                                                    :<|> Named
                                                                                           '("get-config",
                                                                                             MLSConfig)
                                                                                           (Summary
                                                                                              "[deprecated] Get feature config for feature mls"
                                                                                            :> (Until
                                                                                                  'V2
                                                                                                :> (Description
                                                                                                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                                    :> (ZUser
                                                                                                        :> (CanThrow
                                                                                                              'NotATeamMember
                                                                                                            :> (CanThrow
                                                                                                                  OperationDenied
                                                                                                                :> (CanThrow
                                                                                                                      'TeamNotFound
                                                                                                                    :> ("feature-configs"
                                                                                                                        :> ("mls"
                                                                                                                            :> Get
                                                                                                                                 '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     '("get-deprecated", SearchVisibilityAvailableConfig)
     (ZUser
      :> (Summary "[deprecated] Get config for searchVisibility"
          :> (Until 'V2
              :> (Description
                    "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("search-visibility"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      SearchVisibilityAvailableConfig))))))))))))
   :<|> (Named
           '("put-deprecated", SearchVisibilityAvailableConfig)
           (ZUser
            :> (Summary "[deprecated] Get config for searchVisibility"
                :> (Until 'V2
                    :> (Description
                          "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> (CanThrow TeamFeatureError
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("search-visibility"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 SearchVisibilityAvailableConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SearchVisibilityAvailableConfig))))))))))))))
         :<|> (Named
                 '("get-deprecated", ValidateSAMLEmailsConfig)
                 (ZUser
                  :> (Summary "[deprecated] Get config for validateSAMLemails"
                      :> (Until 'V2
                          :> (Description
                                "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow OperationDenied
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("validate-saml-emails"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  ValidateSAMLEmailsConfig))))))))))))
               :<|> Named
                      '("get-deprecated", DigitalSignaturesConfig)
                      (ZUser
                       :> (Summary "[deprecated] Get config for digitalSignatures"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'TeamNotFound
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("digital-signatures"
                                                               :> Get
                                                                    '[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 DeprecatedFeatureAPI GalleyEffects
deprecatedFeatureConfigAPI
    API
  (Named
     '("get-deprecated", SearchVisibilityAvailableConfig)
     (ZUser
      :> (Summary "[deprecated] Get config for searchVisibility"
          :> (Until 'V2
              :> (Description
                    "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("search-visibility"
                                              :> Get
                                                   '[JSON]
                                                   (LockableFeature
                                                      SearchVisibilityAvailableConfig))))))))))))
   :<|> (Named
           '("put-deprecated", SearchVisibilityAvailableConfig)
           (ZUser
            :> (Summary "[deprecated] Get config for searchVisibility"
                :> (Until 'V2
                    :> (Description
                          "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> (CanThrow TeamFeatureError
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("search-visibility"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 SearchVisibilityAvailableConfig)
                                                            :> Put
                                                                 '[JSON]
                                                                 (LockableFeature
                                                                    SearchVisibilityAvailableConfig))))))))))))))
         :<|> (Named
                 '("get-deprecated", ValidateSAMLEmailsConfig)
                 (ZUser
                  :> (Summary "[deprecated] Get config for validateSAMLemails"
                      :> (Until 'V2
                          :> (Description
                                "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow OperationDenied
                                      :> (CanThrow 'TeamNotFound
                                          :> ("teams"
                                              :> (Capture "tid" TeamId
                                                  :> ("features"
                                                      :> ("validate-saml-emails"
                                                          :> Get
                                                               '[JSON]
                                                               (LockableFeature
                                                                  ValidateSAMLEmailsConfig))))))))))))
               :<|> Named
                      '("get-deprecated", DigitalSignaturesConfig)
                      (ZUser
                       :> (Summary "[deprecated] Get config for digitalSignatures"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (CanThrow 'NotATeamMember
                                       :> (CanThrow OperationDenied
                                           :> (CanThrow 'TeamNotFound
                                               :> ("teams"
                                                   :> (Capture "tid" TeamId
                                                       :> ("features"
                                                           :> ("digital-signatures"
                                                               :> Get
                                                                    '[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
        '("get-config", LegalholdConfig)
        (Summary "[deprecated] Get feature config for feature legalhold"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("legalhold"
                                         :> Get '[JSON] (LockableFeature LegalholdConfig))))))))))
      :<|> (Named
              '("get-config", SSOConfig)
              (Summary "[deprecated] Get feature config for feature sso"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("sso"
                                               :> Get '[JSON] (LockableFeature SSOConfig))))))))))
            :<|> (Named
                    '("get-config", SearchVisibilityAvailableConfig)
                    (Summary
                       "[deprecated] Get feature config for feature searchVisibility"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("searchVisibility"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             SearchVisibilityAvailableConfig))))))))))
                  :<|> (Named
                          '("get-config", ValidateSAMLEmailsConfig)
                          (Summary
                             "[deprecated] Get feature config for feature validateSAMLemails"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("validateSAMLemails"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   ValidateSAMLEmailsConfig))))))))))
                        :<|> (Named
                                '("get-config", DigitalSignaturesConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature digitalSignatures"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("digitalSignatures"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         DigitalSignaturesConfig))))))))))
                              :<|> (Named
                                      '("get-config", AppLockConfig)
                                      (Summary "[deprecated] Get feature config for feature appLock"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("appLock"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               AppLockConfig))))))))))
                                    :<|> (Named
                                            '("get-config", FileSharingConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature fileSharing"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("fileSharing"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     FileSharingConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", ClassifiedDomainsConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature classifiedDomains"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("classifiedDomains"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ClassifiedDomainsConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", ConferenceCallingConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature conferenceCalling"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("conferenceCalling"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 ConferenceCallingConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                SelfDeletingMessagesConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature selfDeletingMessages"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("selfDeletingMessages"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       SelfDeletingMessagesConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      GuestLinksConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("conversationGuestLinks"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             GuestLinksConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            SndFactorPasswordChallengeConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   SndFactorPasswordChallengeConfig))))))))))
                                                                        :<|> Named
                                                                               '("get-config",
                                                                                 MLSConfig)
                                                                               (Summary
                                                                                  "[deprecated] Get feature config for feature mls"
                                                                                :> (Until 'V2
                                                                                    :> (Description
                                                                                          "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                        :> (ZUser
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      OperationDenied
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> ("feature-configs"
                                                                                                            :> ("mls"
                                                                                                                :> Get
                                                                                                                     '[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
         '("get-deprecated", SearchVisibilityAvailableConfig)
         (ZUser
          :> (Summary "[deprecated] Get config for searchVisibility"
              :> (Until 'V2
                  :> (Description
                        "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                      :> (CanThrow 'NotATeamMember
                          :> (CanThrow OperationDenied
                              :> (CanThrow 'TeamNotFound
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("search-visibility"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature
                                                          SearchVisibilityAvailableConfig))))))))))))
       :<|> (Named
               '("put-deprecated", SearchVisibilityAvailableConfig)
               (ZUser
                :> (Summary "[deprecated] Get config for searchVisibility"
                    :> (Until 'V2
                        :> (Description
                              "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                            :> (CanThrow 'NotATeamMember
                                :> (CanThrow OperationDenied
                                    :> (CanThrow 'TeamNotFound
                                        :> (CanThrow TeamFeatureError
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("search-visibility"
                                                            :> (ReqBody
                                                                  '[JSON]
                                                                  (Feature
                                                                     SearchVisibilityAvailableConfig)
                                                                :> Put
                                                                     '[JSON]
                                                                     (LockableFeature
                                                                        SearchVisibilityAvailableConfig))))))))))))))
             :<|> (Named
                     '("get-deprecated", ValidateSAMLEmailsConfig)
                     (ZUser
                      :> (Summary "[deprecated] Get config for validateSAMLemails"
                          :> (Until 'V2
                              :> (Description
                                    "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                  :> (CanThrow 'NotATeamMember
                                      :> (CanThrow OperationDenied
                                          :> (CanThrow 'TeamNotFound
                                              :> ("teams"
                                                  :> (Capture "tid" TeamId
                                                      :> ("features"
                                                          :> ("validate-saml-emails"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      ValidateSAMLEmailsConfig))))))))))))
                   :<|> Named
                          '("get-deprecated", DigitalSignaturesConfig)
                          (ZUser
                           :> (Summary "[deprecated] Get config for digitalSignatures"
                               :> (Until 'V2
                                   :> (Description
                                         "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("teams"
                                                       :> (Capture "tid" TeamId
                                                           :> ("features"
                                                               :> ("digital-signatures"
                                                                   :> Get
                                                                        '[JSON]
                                                                        (LockableFeature
                                                                           DigitalSignaturesConfig)))))))))))))))
      :<|> (Named
              '("get-config", LegalholdConfig)
              (Summary "[deprecated] Get feature config for feature legalhold"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("legalhold"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature LegalholdConfig))))))))))
            :<|> (Named
                    '("get-config", SSOConfig)
                    (Summary "[deprecated] Get feature config for feature sso"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("sso"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature SSOConfig))))))))))
                  :<|> (Named
                          '("get-config", SearchVisibilityAvailableConfig)
                          (Summary
                             "[deprecated] Get feature config for feature searchVisibility"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("searchVisibility"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   SearchVisibilityAvailableConfig))))))))))
                        :<|> (Named
                                '("get-config", ValidateSAMLEmailsConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature validateSAMLemails"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("validateSAMLemails"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ValidateSAMLEmailsConfig))))))))))
                              :<|> (Named
                                      '("get-config", DigitalSignaturesConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature digitalSignatures"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("digitalSignatures"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               DigitalSignaturesConfig))))))))))
                                    :<|> (Named
                                            '("get-config", AppLockConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature appLock"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("appLock"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     AppLockConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", FileSharingConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature fileSharing"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("fileSharing"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           FileSharingConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", ClassifiedDomainsConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature classifiedDomains"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("classifiedDomains"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 ClassifiedDomainsConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                ConferenceCallingConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature conferenceCalling"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("conferenceCalling"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       ConferenceCallingConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      SelfDeletingMessagesConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature selfDeletingMessages"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("selfDeletingMessages"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             SelfDeletingMessagesConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            GuestLinksConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("conversationGuestLinks"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   GuestLinksConfig))))))))))
                                                                        :<|> (Named
                                                                                '("get-config",
                                                                                  SndFactorPasswordChallengeConfig)
                                                                                (Summary
                                                                                   "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                                 :> (Until 'V2
                                                                                     :> (Description
                                                                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                         :> (ZUser
                                                                                             :> (CanThrow
                                                                                                   'NotATeamMember
                                                                                                 :> (CanThrow
                                                                                                       OperationDenied
                                                                                                     :> (CanThrow
                                                                                                           'TeamNotFound
                                                                                                         :> ("feature-configs"
                                                                                                             :> ("sndFactorPasswordChallenge"
                                                                                                                 :> Get
                                                                                                                      '[JSON]
                                                                                                                      (LockableFeature
                                                                                                                         SndFactorPasswordChallengeConfig))))))))))
                                                                              :<|> Named
                                                                                     '("get-config",
                                                                                       MLSConfig)
                                                                                     (Summary
                                                                                        "[deprecated] Get feature config for feature mls"
                                                                                      :> (Until 'V2
                                                                                          :> (Description
                                                                                                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                              :> (ZUser
                                                                                                  :> (CanThrow
                                                                                                        'NotATeamMember
                                                                                                      :> (CanThrow
                                                                                                            OperationDenied
                                                                                                          :> (CanThrow
                                                                                                                'TeamNotFound
                                                                                                              :> ("feature-configs"
                                                                                                                  :> ("mls"
                                                                                                                      :> Get
                                                                                                                           '[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 api1 (r :: EffectRow) api2.
API api1 r -> API api2 r -> API (api1 :<|> api2) r
<@> API
  (Named
     '("get-config", LegalholdConfig)
     (Summary "[deprecated] Get feature config for feature legalhold"
      :> (Until 'V2
          :> (Description
                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs"
                                  :> ("legalhold"
                                      :> Get '[JSON] (LockableFeature LegalholdConfig))))))))))
   :<|> (Named
           '("get-config", SSOConfig)
           (Summary "[deprecated] Get feature config for feature sso"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("sso"
                                            :> Get '[JSON] (LockableFeature SSOConfig))))))))))
         :<|> (Named
                 '("get-config", SearchVisibilityAvailableConfig)
                 (Summary
                    "[deprecated] Get feature config for feature searchVisibility"
                  :> (Until 'V2
                      :> (Description
                            "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                          :> (ZUser
                              :> (CanThrow 'NotATeamMember
                                  :> (CanThrow OperationDenied
                                      :> (CanThrow 'TeamNotFound
                                          :> ("feature-configs"
                                              :> ("searchVisibility"
                                                  :> Get
                                                       '[JSON]
                                                       (LockableFeature
                                                          SearchVisibilityAvailableConfig))))))))))
               :<|> (Named
                       '("get-config", ValidateSAMLEmailsConfig)
                       (Summary
                          "[deprecated] Get feature config for feature validateSAMLemails"
                        :> (Until 'V2
                            :> (Description
                                  "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                :> (ZUser
                                    :> (CanThrow 'NotATeamMember
                                        :> (CanThrow OperationDenied
                                            :> (CanThrow 'TeamNotFound
                                                :> ("feature-configs"
                                                    :> ("validateSAMLemails"
                                                        :> Get
                                                             '[JSON]
                                                             (LockableFeature
                                                                ValidateSAMLEmailsConfig))))))))))
                     :<|> (Named
                             '("get-config", DigitalSignaturesConfig)
                             (Summary
                                "[deprecated] Get feature config for feature digitalSignatures"
                              :> (Until 'V2
                                  :> (Description
                                        "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                      :> (ZUser
                                          :> (CanThrow 'NotATeamMember
                                              :> (CanThrow OperationDenied
                                                  :> (CanThrow 'TeamNotFound
                                                      :> ("feature-configs"
                                                          :> ("digitalSignatures"
                                                              :> Get
                                                                   '[JSON]
                                                                   (LockableFeature
                                                                      DigitalSignaturesConfig))))))))))
                           :<|> (Named
                                   '("get-config", AppLockConfig)
                                   (Summary "[deprecated] Get feature config for feature appLock"
                                    :> (Until 'V2
                                        :> (Description
                                              "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                            :> (ZUser
                                                :> (CanThrow 'NotATeamMember
                                                    :> (CanThrow OperationDenied
                                                        :> (CanThrow 'TeamNotFound
                                                            :> ("feature-configs"
                                                                :> ("appLock"
                                                                    :> Get
                                                                         '[JSON]
                                                                         (LockableFeature
                                                                            AppLockConfig))))))))))
                                 :<|> (Named
                                         '("get-config", FileSharingConfig)
                                         (Summary
                                            "[deprecated] Get feature config for feature fileSharing"
                                          :> (Until 'V2
                                              :> (Description
                                                    "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                  :> (ZUser
                                                      :> (CanThrow 'NotATeamMember
                                                          :> (CanThrow OperationDenied
                                                              :> (CanThrow 'TeamNotFound
                                                                  :> ("feature-configs"
                                                                      :> ("fileSharing"
                                                                          :> Get
                                                                               '[JSON]
                                                                               (LockableFeature
                                                                                  FileSharingConfig))))))))))
                                       :<|> (Named
                                               '("get-config", ClassifiedDomainsConfig)
                                               (Summary
                                                  "[deprecated] Get feature config for feature classifiedDomains"
                                                :> (Until 'V2
                                                    :> (Description
                                                          "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                        :> (ZUser
                                                            :> (CanThrow 'NotATeamMember
                                                                :> (CanThrow OperationDenied
                                                                    :> (CanThrow 'TeamNotFound
                                                                        :> ("feature-configs"
                                                                            :> ("classifiedDomains"
                                                                                :> Get
                                                                                     '[JSON]
                                                                                     (LockableFeature
                                                                                        ClassifiedDomainsConfig))))))))))
                                             :<|> (Named
                                                     '("get-config", ConferenceCallingConfig)
                                                     (Summary
                                                        "[deprecated] Get feature config for feature conferenceCalling"
                                                      :> (Until 'V2
                                                          :> (Description
                                                                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                              :> (ZUser
                                                                  :> (CanThrow 'NotATeamMember
                                                                      :> (CanThrow OperationDenied
                                                                          :> (CanThrow 'TeamNotFound
                                                                              :> ("feature-configs"
                                                                                  :> ("conferenceCalling"
                                                                                      :> Get
                                                                                           '[JSON]
                                                                                           (LockableFeature
                                                                                              ConferenceCallingConfig))))))))))
                                                   :<|> (Named
                                                           '("get-config",
                                                             SelfDeletingMessagesConfig)
                                                           (Summary
                                                              "[deprecated] Get feature config for feature selfDeletingMessages"
                                                            :> (Until 'V2
                                                                :> (Description
                                                                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                    :> (ZUser
                                                                        :> (CanThrow 'NotATeamMember
                                                                            :> (CanThrow
                                                                                  OperationDenied
                                                                                :> (CanThrow
                                                                                      'TeamNotFound
                                                                                    :> ("feature-configs"
                                                                                        :> ("selfDeletingMessages"
                                                                                            :> Get
                                                                                                 '[JSON]
                                                                                                 (LockableFeature
                                                                                                    SelfDeletingMessagesConfig))))))))))
                                                         :<|> (Named
                                                                 '("get-config", GuestLinksConfig)
                                                                 (Summary
                                                                    "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                  :> (Until 'V2
                                                                      :> (Description
                                                                            "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                          :> (ZUser
                                                                              :> (CanThrow
                                                                                    'NotATeamMember
                                                                                  :> (CanThrow
                                                                                        OperationDenied
                                                                                      :> (CanThrow
                                                                                            'TeamNotFound
                                                                                          :> ("feature-configs"
                                                                                              :> ("conversationGuestLinks"
                                                                                                  :> Get
                                                                                                       '[JSON]
                                                                                                       (LockableFeature
                                                                                                          GuestLinksConfig))))))))))
                                                               :<|> (Named
                                                                       '("get-config",
                                                                         SndFactorPasswordChallengeConfig)
                                                                       (Summary
                                                                          "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                        :> (Until 'V2
                                                                            :> (Description
                                                                                  "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                :> (ZUser
                                                                                    :> (CanThrow
                                                                                          'NotATeamMember
                                                                                        :> (CanThrow
                                                                                              OperationDenied
                                                                                            :> (CanThrow
                                                                                                  'TeamNotFound
                                                                                                :> ("feature-configs"
                                                                                                    :> ("sndFactorPasswordChallenge"
                                                                                                        :> Get
                                                                                                             '[JSON]
                                                                                                             (LockableFeature
                                                                                                                SndFactorPasswordChallengeConfig))))))))))
                                                                     :<|> Named
                                                                            '("get-config",
                                                                              MLSConfig)
                                                                            (Summary
                                                                               "[deprecated] Get feature config for feature mls"
                                                                             :> (Until 'V2
                                                                                 :> (Description
                                                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                     :> (ZUser
                                                                                         :> (CanThrow
                                                                                               'NotATeamMember
                                                                                             :> (CanThrow
                                                                                                   OperationDenied
                                                                                                 :> (CanThrow
                                                                                                       'TeamNotFound
                                                                                                     :> ("feature-configs"
                                                                                                         :> ("mls"
                                                                                                             :> Get
                                                                                                                  '[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
  (AllDeprecatedFeatureConfigAPI DeprecatedFeatureConfigs)
  GalleyEffects
deprecatedFeatureAPI

deprecatedFeatureConfigAPI :: API DeprecatedFeatureAPI GalleyEffects
deprecatedFeatureConfigAPI :: API DeprecatedFeatureAPI GalleyEffects
deprecatedFeatureConfigAPI =
  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-deprecated", SearchVisibilityAvailableConfig) ServerT
  (ZUser
   :> (Summary "[deprecated] Get config for searchVisibility"
       :> (Until 'V2
           :> (Description
                 "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("search-visibility"
                                           :> Get
                                                '[JSON]
                                                (LockableFeature
                                                   SearchVisibilityAvailableConfig))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (ZUser
            :> (Summary "[deprecated] Get config for searchVisibility"
                :> (Until 'V2
                    :> (Description
                          "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("search-visibility"
                                                    :> Get
                                                         '[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]))
UserId
-> TeamId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature SearchVisibilityAvailableConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member TeamFeatureStore r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member TeamStore r) =>
UserId -> TeamId -> Sem r (LockableFeature cfg)
getFeature
    API
  (Named
     '("get-deprecated", SearchVisibilityAvailableConfig)
     (ZUser
      :> (Summary "[deprecated] Get config for searchVisibility"
          :> (Until 'V2
              :> (Description
                    "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("search-visibility"
                                              :> Get
                                                   '[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
        '("put-deprecated", SearchVisibilityAvailableConfig)
        (ZUser
         :> (Summary "[deprecated] Get config for searchVisibility"
             :> (Until 'V2
                 :> (Description
                       "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> ("teams"
                                         :> (Capture "tid" TeamId
                                             :> ("features"
                                                 :> ("search-visibility"
                                                     :> (ReqBody
                                                           '[JSON]
                                                           (Feature SearchVisibilityAvailableConfig)
                                                         :> Put
                                                              '[JSON]
                                                              (LockableFeature
                                                                 SearchVisibilityAvailableConfig))))))))))))))
      :<|> (Named
              '("get-deprecated", ValidateSAMLEmailsConfig)
              (ZUser
               :> (Summary "[deprecated] Get config for validateSAMLemails"
                   :> (Until 'V2
                       :> (Description
                             "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("validate-saml-emails"
                                                       :> Get
                                                            '[JSON]
                                                            (LockableFeature
                                                               ValidateSAMLEmailsConfig))))))))))))
            :<|> Named
                   '("get-deprecated", DigitalSignaturesConfig)
                   (ZUser
                    :> (Summary "[deprecated] Get config for digitalSignatures"
                        :> (Until 'V2
                            :> (Description
                                  "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("digital-signatures"
                                                            :> Get
                                                                 '[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
        '("get-deprecated", SearchVisibilityAvailableConfig)
        (ZUser
         :> (Summary "[deprecated] Get config for searchVisibility"
             :> (Until 'V2
                 :> (Description
                       "Deprecated. Please use `GET /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("search-visibility"
                                                 :> Get
                                                      '[JSON]
                                                      (LockableFeature
                                                         SearchVisibilityAvailableConfig))))))))))))
      :<|> (Named
              '("put-deprecated", SearchVisibilityAvailableConfig)
              (ZUser
               :> (Summary "[deprecated] Get config for searchVisibility"
                   :> (Until 'V2
                       :> (Description
                             "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> (CanThrow TeamFeatureError
                                           :> ("teams"
                                               :> (Capture "tid" TeamId
                                                   :> ("features"
                                                       :> ("search-visibility"
                                                           :> (ReqBody
                                                                 '[JSON]
                                                                 (Feature
                                                                    SearchVisibilityAvailableConfig)
                                                               :> Put
                                                                    '[JSON]
                                                                    (LockableFeature
                                                                       SearchVisibilityAvailableConfig))))))))))))))
            :<|> (Named
                    '("get-deprecated", ValidateSAMLEmailsConfig)
                    (ZUser
                     :> (Summary "[deprecated] Get config for validateSAMLemails"
                         :> (Until 'V2
                             :> (Description
                                   "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("teams"
                                                 :> (Capture "tid" TeamId
                                                     :> ("features"
                                                         :> ("validate-saml-emails"
                                                             :> Get
                                                                  '[JSON]
                                                                  (LockableFeature
                                                                     ValidateSAMLEmailsConfig))))))))))))
                  :<|> Named
                         '("get-deprecated", DigitalSignaturesConfig)
                         (ZUser
                          :> (Summary "[deprecated] Get config for digitalSignatures"
                              :> (Until 'V2
                                  :> (Description
                                        "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("teams"
                                                      :> (Capture "tid" TeamId
                                                          :> ("features"
                                                              :> ("digital-signatures"
                                                                  :> Get
                                                                       '[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 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-deprecated", SearchVisibilityAvailableConfig) ServerT
  (ZUser
   :> (Summary "[deprecated] Get config for searchVisibility"
       :> (Until 'V2
           :> (Description
                 "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> (CanThrow TeamFeatureError
                               :> ("teams"
                                   :> (Capture "tid" TeamId
                                       :> ("features"
                                           :> ("search-visibility"
                                               :> (ReqBody
                                                     '[JSON]
                                                     (Feature SearchVisibilityAvailableConfig)
                                                   :> Put
                                                        '[JSON]
                                                        (LockableFeature
                                                           SearchVisibilityAvailableConfig))))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (ZUser
            :> (Summary "[deprecated] Get config for searchVisibility"
                :> (Until 'V2
                    :> (Description
                          "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> (CanThrow TeamFeatureError
                                        :> ("teams"
                                            :> (Capture "tid" TeamId
                                                :> ("features"
                                                    :> ("search-visibility"
                                                        :> (ReqBody
                                                              '[JSON]
                                                              (Feature
                                                                 SearchVisibilityAvailableConfig)
                                                            :> Put
                                                                 '[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]))
UserId
-> TeamId
-> Feature SearchVisibilityAvailableConfig
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       Error TeamFeatureError, BrigAccess, SparAccess,
       NotificationSubsystem, GundeckAPIAccess, Rpc, ExternalAccess,
       FederatorAccess, BackendNotificationQueueAccess, BotAccess,
       FireAndForget, ClientStore, CodeStore, ProposalStore,
       ConversationStore, SubConversationStore, Random,
       CustomBackendStore, TeamFeatureStore, LegalHoldStore, MemberStore,
       SearchVisibilityStore, ServiceStore, TeamNotificationStore,
       TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (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)
forall cfg (r :: EffectRow).
(SetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 SetFeatureForTeamConstraints cfg r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged OperationDenied ())) r,
 Member (Error TeamFeatureError) r, Member (Input Opts) r,
 Member TeamStore r, Member TeamFeatureStore r,
 Member (Logger (Msg -> Msg)) r, Member NotificationSubsystem r) =>
UserId -> TeamId -> Feature cfg -> Sem r (LockableFeature cfg)
setFeature
    API
  (Named
     '("put-deprecated", SearchVisibilityAvailableConfig)
     (ZUser
      :> (Summary "[deprecated] Get config for searchVisibility"
          :> (Until 'V2
              :> (Description
                    "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> (CanThrow TeamFeatureError
                                  :> ("teams"
                                      :> (Capture "tid" TeamId
                                          :> ("features"
                                              :> ("search-visibility"
                                                  :> (ReqBody
                                                        '[JSON]
                                                        (Feature SearchVisibilityAvailableConfig)
                                                      :> Put
                                                           '[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
        '("get-deprecated", ValidateSAMLEmailsConfig)
        (ZUser
         :> (Summary "[deprecated] Get config for validateSAMLemails"
             :> (Until 'V2
                 :> (Description
                       "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("validate-saml-emails"
                                                 :> Get
                                                      '[JSON]
                                                      (LockableFeature
                                                         ValidateSAMLEmailsConfig))))))))))))
      :<|> Named
             '("get-deprecated", DigitalSignaturesConfig)
             (ZUser
              :> (Summary "[deprecated] Get config for digitalSignatures"
                  :> (Until 'V2
                      :> (Description
                            "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("digital-signatures"
                                                      :> Get
                                                           '[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
        '("put-deprecated", SearchVisibilityAvailableConfig)
        (ZUser
         :> (Summary "[deprecated] Get config for searchVisibility"
             :> (Until 'V2
                 :> (Description
                       "Deprecated. Please use `PUT /teams/:tid/features/searchVisibility` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> (CanThrow TeamFeatureError
                                     :> ("teams"
                                         :> (Capture "tid" TeamId
                                             :> ("features"
                                                 :> ("search-visibility"
                                                     :> (ReqBody
                                                           '[JSON]
                                                           (Feature SearchVisibilityAvailableConfig)
                                                         :> Put
                                                              '[JSON]
                                                              (LockableFeature
                                                                 SearchVisibilityAvailableConfig))))))))))))))
      :<|> (Named
              '("get-deprecated", ValidateSAMLEmailsConfig)
              (ZUser
               :> (Summary "[deprecated] Get config for validateSAMLemails"
                   :> (Until 'V2
                       :> (Description
                             "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("teams"
                                           :> (Capture "tid" TeamId
                                               :> ("features"
                                                   :> ("validate-saml-emails"
                                                       :> Get
                                                            '[JSON]
                                                            (LockableFeature
                                                               ValidateSAMLEmailsConfig))))))))))))
            :<|> Named
                   '("get-deprecated", DigitalSignaturesConfig)
                   (ZUser
                    :> (Summary "[deprecated] Get config for digitalSignatures"
                        :> (Until 'V2
                            :> (Description
                                  "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'TeamNotFound
                                            :> ("teams"
                                                :> (Capture "tid" TeamId
                                                    :> ("features"
                                                        :> ("digital-signatures"
                                                            :> Get
                                                                 '[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 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-deprecated", ValidateSAMLEmailsConfig) ServerT
  (ZUser
   :> (Summary "[deprecated] Get config for validateSAMLemails"
       :> (Until 'V2
           :> (Description
                 "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("validate-saml-emails"
                                           :> Get
                                                '[JSON]
                                                (LockableFeature
                                                   ValidateSAMLEmailsConfig))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (ZUser
            :> (Summary "[deprecated] Get config for validateSAMLemails"
                :> (Until 'V2
                    :> (Description
                          "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("validate-saml-emails"
                                                    :> Get
                                                         '[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]))
UserId
-> TeamId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature ValidateSAMLEmailsConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member TeamFeatureStore r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member TeamStore r) =>
UserId -> TeamId -> Sem r (LockableFeature cfg)
getFeature
    API
  (Named
     '("get-deprecated", ValidateSAMLEmailsConfig)
     (ZUser
      :> (Summary "[deprecated] Get config for validateSAMLemails"
          :> (Until 'V2
              :> (Description
                    "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("teams"
                                  :> (Capture "tid" TeamId
                                      :> ("features"
                                          :> ("validate-saml-emails"
                                              :> Get
                                                   '[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
        '("get-deprecated", DigitalSignaturesConfig)
        (ZUser
         :> (Summary "[deprecated] Get config for digitalSignatures"
             :> (Until 'V2
                 :> (Description
                       "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("digital-signatures"
                                                 :> Get
                                                      '[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
        '("get-deprecated", ValidateSAMLEmailsConfig)
        (ZUser
         :> (Summary "[deprecated] Get config for validateSAMLemails"
             :> (Until 'V2
                 :> (Description
                       "Deprecated. Please use `GET /teams/:tid/features/validateSAMLemails` instead.\nThis endpoint is potentially used by the old Android client. It is not used by iOS, team management, or webapp as of June 2022"
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("teams"
                                     :> (Capture "tid" TeamId
                                         :> ("features"
                                             :> ("validate-saml-emails"
                                                 :> Get
                                                      '[JSON]
                                                      (LockableFeature
                                                         ValidateSAMLEmailsConfig))))))))))))
      :<|> Named
             '("get-deprecated", DigitalSignaturesConfig)
             (ZUser
              :> (Summary "[deprecated] Get config for digitalSignatures"
                  :> (Until 'V2
                      :> (Description
                            "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'TeamNotFound
                                      :> ("teams"
                                          :> (Capture "tid" TeamId
                                              :> ("features"
                                                  :> ("digital-signatures"
                                                      :> Get
                                                           '[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 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-deprecated", DigitalSignaturesConfig) ServerT
  (ZUser
   :> (Summary "[deprecated] Get config for digitalSignatures"
       :> (Until 'V2
           :> (Description
                 "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("teams"
                               :> (Capture "tid" TeamId
                                   :> ("features"
                                       :> ("digital-signatures"
                                           :> Get
                                                '[JSON]
                                                (LockableFeature DigitalSignaturesConfig))))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (ZUser
            :> (Summary "[deprecated] Get config for digitalSignatures"
                :> (Until 'V2
                    :> (Description
                          "Deprecated. Please use `GET /teams/:tid/features/digitalSignatures` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("teams"
                                        :> (Capture "tid" TeamId
                                            :> ("features"
                                                :> ("digital-signatures"
                                                    :> Get
                                                         '[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]))
UserId
-> TeamId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature DigitalSignaturesConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, ComputeFeatureConstraints cfg r,
 Member (Input Opts) r, Member TeamFeatureStore r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member TeamStore r) =>
UserId -> TeamId -> Sem r (LockableFeature cfg)
getFeature

deprecatedFeatureAPI :: API (AllDeprecatedFeatureConfigAPI DeprecatedFeatureConfigs) GalleyEffects
deprecatedFeatureAPI :: API
  (AllDeprecatedFeatureConfigAPI DeprecatedFeatureConfigs)
  GalleyEffects
deprecatedFeatureAPI =
  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-config", LegalholdConfig) ServerT
  (Summary "[deprecated] Get feature config for feature legalhold"
   :> (Until 'V2
       :> (Description
             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs"
                               :> ("legalhold"
                                   :> Get '[JSON] (LockableFeature LegalholdConfig))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "[deprecated] Get feature config for feature legalhold"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("legalhold"
                                            :> Get
                                                 '[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]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature LegalholdConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, GetFeatureForUserConstraints cfg r,
 ComputeFeatureConstraints cfg r) =>
UserId -> Sem r (LockableFeature cfg)
getSingleFeatureForUser
    API
  (Named
     '("get-config", LegalholdConfig)
     (Summary "[deprecated] Get feature config for feature legalhold"
      :> (Until 'V2
          :> (Description
                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs"
                                  :> ("legalhold"
                                      :> Get '[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
        '("get-config", SSOConfig)
        (Summary "[deprecated] Get feature config for feature sso"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("sso" :> Get '[JSON] (LockableFeature SSOConfig))))))))))
      :<|> (Named
              '("get-config", SearchVisibilityAvailableConfig)
              (Summary
                 "[deprecated] Get feature config for feature searchVisibility"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("searchVisibility"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       SearchVisibilityAvailableConfig))))))))))
            :<|> (Named
                    '("get-config", ValidateSAMLEmailsConfig)
                    (Summary
                       "[deprecated] Get feature config for feature validateSAMLemails"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("validateSAMLemails"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             ValidateSAMLEmailsConfig))))))))))
                  :<|> (Named
                          '("get-config", DigitalSignaturesConfig)
                          (Summary
                             "[deprecated] Get feature config for feature digitalSignatures"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("digitalSignatures"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   DigitalSignaturesConfig))))))))))
                        :<|> (Named
                                '("get-config", AppLockConfig)
                                (Summary "[deprecated] Get feature config for feature appLock"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("appLock"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         AppLockConfig))))))))))
                              :<|> (Named
                                      '("get-config", FileSharingConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature fileSharing"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("fileSharing"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               FileSharingConfig))))))))))
                                    :<|> (Named
                                            '("get-config", ClassifiedDomainsConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature classifiedDomains"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("classifiedDomains"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ClassifiedDomainsConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", ConferenceCallingConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature conferenceCalling"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("conferenceCalling"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ConferenceCallingConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", SelfDeletingMessagesConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature selfDeletingMessages"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("selfDeletingMessages"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 SelfDeletingMessagesConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config", GuestLinksConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature conversationGuestLinks"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("conversationGuestLinks"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       GuestLinksConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      SndFactorPasswordChallengeConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             SndFactorPasswordChallengeConfig))))))))))
                                                                  :<|> Named
                                                                         '("get-config", MLSConfig)
                                                                         (Summary
                                                                            "[deprecated] Get feature config for feature mls"
                                                                          :> (Until 'V2
                                                                              :> (Description
                                                                                    "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                  :> (ZUser
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                OperationDenied
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("feature-configs"
                                                                                                      :> ("mls"
                                                                                                          :> Get
                                                                                                               '[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
        '("get-config", LegalholdConfig)
        (Summary "[deprecated] Get feature config for feature legalhold"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("legalhold"
                                         :> Get '[JSON] (LockableFeature LegalholdConfig))))))))))
      :<|> (Named
              '("get-config", SSOConfig)
              (Summary "[deprecated] Get feature config for feature sso"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("sso"
                                               :> Get '[JSON] (LockableFeature SSOConfig))))))))))
            :<|> (Named
                    '("get-config", SearchVisibilityAvailableConfig)
                    (Summary
                       "[deprecated] Get feature config for feature searchVisibility"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("searchVisibility"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             SearchVisibilityAvailableConfig))))))))))
                  :<|> (Named
                          '("get-config", ValidateSAMLEmailsConfig)
                          (Summary
                             "[deprecated] Get feature config for feature validateSAMLemails"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("validateSAMLemails"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   ValidateSAMLEmailsConfig))))))))))
                        :<|> (Named
                                '("get-config", DigitalSignaturesConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature digitalSignatures"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("digitalSignatures"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         DigitalSignaturesConfig))))))))))
                              :<|> (Named
                                      '("get-config", AppLockConfig)
                                      (Summary "[deprecated] Get feature config for feature appLock"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("appLock"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               AppLockConfig))))))))))
                                    :<|> (Named
                                            '("get-config", FileSharingConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature fileSharing"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("fileSharing"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     FileSharingConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", ClassifiedDomainsConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature classifiedDomains"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("classifiedDomains"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ClassifiedDomainsConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", ConferenceCallingConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature conferenceCalling"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("conferenceCalling"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 ConferenceCallingConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                SelfDeletingMessagesConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature selfDeletingMessages"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("selfDeletingMessages"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       SelfDeletingMessagesConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      GuestLinksConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature conversationGuestLinks"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("conversationGuestLinks"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             GuestLinksConfig))))))))))
                                                                  :<|> (Named
                                                                          '("get-config",
                                                                            SndFactorPasswordChallengeConfig)
                                                                          (Summary
                                                                             "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                           :> (Until 'V2
                                                                               :> (Description
                                                                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                   :> (ZUser
                                                                                       :> (CanThrow
                                                                                             'NotATeamMember
                                                                                           :> (CanThrow
                                                                                                 OperationDenied
                                                                                               :> (CanThrow
                                                                                                     'TeamNotFound
                                                                                                   :> ("feature-configs"
                                                                                                       :> ("sndFactorPasswordChallenge"
                                                                                                           :> Get
                                                                                                                '[JSON]
                                                                                                                (LockableFeature
                                                                                                                   SndFactorPasswordChallengeConfig))))))))))
                                                                        :<|> Named
                                                                               '("get-config",
                                                                                 MLSConfig)
                                                                               (Summary
                                                                                  "[deprecated] Get feature config for feature mls"
                                                                                :> (Until 'V2
                                                                                    :> (Description
                                                                                          "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                        :> (ZUser
                                                                                            :> (CanThrow
                                                                                                  'NotATeamMember
                                                                                                :> (CanThrow
                                                                                                      OperationDenied
                                                                                                    :> (CanThrow
                                                                                                          'TeamNotFound
                                                                                                        :> ("feature-configs"
                                                                                                            :> ("mls"
                                                                                                                :> Get
                                                                                                                     '[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 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-config", SSOConfig) ServerT
  (Summary "[deprecated] Get feature config for feature sso"
   :> (Until 'V2
       :> (Description
             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs"
                               :> ("sso" :> Get '[JSON] (LockableFeature SSOConfig))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "[deprecated] Get feature config for feature sso"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("sso"
                                            :> Get '[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]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature SSOConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, GetFeatureForUserConstraints cfg r,
 ComputeFeatureConstraints cfg r) =>
UserId -> Sem r (LockableFeature cfg)
getSingleFeatureForUser
    API
  (Named
     '("get-config", SSOConfig)
     (Summary "[deprecated] Get feature config for feature sso"
      :> (Until 'V2
          :> (Description
                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs"
                                  :> ("sso" :> Get '[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
        '("get-config", SearchVisibilityAvailableConfig)
        (Summary
           "[deprecated] Get feature config for feature searchVisibility"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("searchVisibility"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature
                                                 SearchVisibilityAvailableConfig))))))))))
      :<|> (Named
              '("get-config", ValidateSAMLEmailsConfig)
              (Summary
                 "[deprecated] Get feature config for feature validateSAMLemails"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("validateSAMLemails"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       ValidateSAMLEmailsConfig))))))))))
            :<|> (Named
                    '("get-config", DigitalSignaturesConfig)
                    (Summary
                       "[deprecated] Get feature config for feature digitalSignatures"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("digitalSignatures"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             DigitalSignaturesConfig))))))))))
                  :<|> (Named
                          '("get-config", AppLockConfig)
                          (Summary "[deprecated] Get feature config for feature appLock"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("appLock"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   AppLockConfig))))))))))
                        :<|> (Named
                                '("get-config", FileSharingConfig)
                                (Summary "[deprecated] Get feature config for feature fileSharing"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("fileSharing"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         FileSharingConfig))))))))))
                              :<|> (Named
                                      '("get-config", ClassifiedDomainsConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature classifiedDomains"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("classifiedDomains"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ClassifiedDomainsConfig))))))))))
                                    :<|> (Named
                                            '("get-config", ConferenceCallingConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature conferenceCalling"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("conferenceCalling"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ConferenceCallingConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", SelfDeletingMessagesConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature selfDeletingMessages"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("selfDeletingMessages"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           SelfDeletingMessagesConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", GuestLinksConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature conversationGuestLinks"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("conversationGuestLinks"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 GuestLinksConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                SndFactorPasswordChallengeConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       SndFactorPasswordChallengeConfig))))))))))
                                                            :<|> Named
                                                                   '("get-config", MLSConfig)
                                                                   (Summary
                                                                      "[deprecated] Get feature config for feature mls"
                                                                    :> (Until 'V2
                                                                        :> (Description
                                                                              "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                            :> (ZUser
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          OperationDenied
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("feature-configs"
                                                                                                :> ("mls"
                                                                                                    :> Get
                                                                                                         '[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
        '("get-config", SSOConfig)
        (Summary "[deprecated] Get feature config for feature sso"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("sso" :> Get '[JSON] (LockableFeature SSOConfig))))))))))
      :<|> (Named
              '("get-config", SearchVisibilityAvailableConfig)
              (Summary
                 "[deprecated] Get feature config for feature searchVisibility"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("searchVisibility"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       SearchVisibilityAvailableConfig))))))))))
            :<|> (Named
                    '("get-config", ValidateSAMLEmailsConfig)
                    (Summary
                       "[deprecated] Get feature config for feature validateSAMLemails"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("validateSAMLemails"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             ValidateSAMLEmailsConfig))))))))))
                  :<|> (Named
                          '("get-config", DigitalSignaturesConfig)
                          (Summary
                             "[deprecated] Get feature config for feature digitalSignatures"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("digitalSignatures"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   DigitalSignaturesConfig))))))))))
                        :<|> (Named
                                '("get-config", AppLockConfig)
                                (Summary "[deprecated] Get feature config for feature appLock"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("appLock"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         AppLockConfig))))))))))
                              :<|> (Named
                                      '("get-config", FileSharingConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature fileSharing"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("fileSharing"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               FileSharingConfig))))))))))
                                    :<|> (Named
                                            '("get-config", ClassifiedDomainsConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature classifiedDomains"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("classifiedDomains"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ClassifiedDomainsConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", ConferenceCallingConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature conferenceCalling"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("conferenceCalling"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           ConferenceCallingConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", SelfDeletingMessagesConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature selfDeletingMessages"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("selfDeletingMessages"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 SelfDeletingMessagesConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config", GuestLinksConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature conversationGuestLinks"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("conversationGuestLinks"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       GuestLinksConfig))))))))))
                                                            :<|> (Named
                                                                    '("get-config",
                                                                      SndFactorPasswordChallengeConfig)
                                                                    (Summary
                                                                       "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                                     :> (Until 'V2
                                                                         :> (Description
                                                                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                             :> (ZUser
                                                                                 :> (CanThrow
                                                                                       'NotATeamMember
                                                                                     :> (CanThrow
                                                                                           OperationDenied
                                                                                         :> (CanThrow
                                                                                               'TeamNotFound
                                                                                             :> ("feature-configs"
                                                                                                 :> ("sndFactorPasswordChallenge"
                                                                                                     :> Get
                                                                                                          '[JSON]
                                                                                                          (LockableFeature
                                                                                                             SndFactorPasswordChallengeConfig))))))))))
                                                                  :<|> Named
                                                                         '("get-config", MLSConfig)
                                                                         (Summary
                                                                            "[deprecated] Get feature config for feature mls"
                                                                          :> (Until 'V2
                                                                              :> (Description
                                                                                    "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                                  :> (ZUser
                                                                                      :> (CanThrow
                                                                                            'NotATeamMember
                                                                                          :> (CanThrow
                                                                                                OperationDenied
                                                                                              :> (CanThrow
                                                                                                    'TeamNotFound
                                                                                                  :> ("feature-configs"
                                                                                                      :> ("mls"
                                                                                                          :> Get
                                                                                                               '[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 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-config", SearchVisibilityAvailableConfig) ServerT
  (Summary
     "[deprecated] Get feature config for feature searchVisibility"
   :> (Until 'V2
       :> (Description
             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs"
                               :> ("searchVisibility"
                                   :> Get
                                        '[JSON]
                                        (LockableFeature SearchVisibilityAvailableConfig))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary
              "[deprecated] Get feature config for feature searchVisibility"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("searchVisibility"
                                            :> Get
                                                 '[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]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature SearchVisibilityAvailableConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, GetFeatureForUserConstraints cfg r,
 ComputeFeatureConstraints cfg r) =>
UserId -> Sem r (LockableFeature cfg)
getSingleFeatureForUser
    API
  (Named
     '("get-config", SearchVisibilityAvailableConfig)
     (Summary
        "[deprecated] Get feature config for feature searchVisibility"
      :> (Until 'V2
          :> (Description
                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs"
                                  :> ("searchVisibility"
                                      :> Get
                                           '[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
        '("get-config", ValidateSAMLEmailsConfig)
        (Summary
           "[deprecated] Get feature config for feature validateSAMLemails"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("validateSAMLemails"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature ValidateSAMLEmailsConfig))))))))))
      :<|> (Named
              '("get-config", DigitalSignaturesConfig)
              (Summary
                 "[deprecated] Get feature config for feature digitalSignatures"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("digitalSignatures"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       DigitalSignaturesConfig))))))))))
            :<|> (Named
                    '("get-config", AppLockConfig)
                    (Summary "[deprecated] Get feature config for feature appLock"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("appLock"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature AppLockConfig))))))))))
                  :<|> (Named
                          '("get-config", FileSharingConfig)
                          (Summary "[deprecated] Get feature config for feature fileSharing"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("fileSharing"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   FileSharingConfig))))))))))
                        :<|> (Named
                                '("get-config", ClassifiedDomainsConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature classifiedDomains"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("classifiedDomains"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ClassifiedDomainsConfig))))))))))
                              :<|> (Named
                                      '("get-config", ConferenceCallingConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature conferenceCalling"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("conferenceCalling"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ConferenceCallingConfig))))))))))
                                    :<|> (Named
                                            '("get-config", SelfDeletingMessagesConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature selfDeletingMessages"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("selfDeletingMessages"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SelfDeletingMessagesConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", GuestLinksConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature conversationGuestLinks"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("conversationGuestLinks"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           GuestLinksConfig))))))))))
                                                :<|> (Named
                                                        '("get-config",
                                                          SndFactorPasswordChallengeConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 SndFactorPasswordChallengeConfig))))))))))
                                                      :<|> Named
                                                             '("get-config", MLSConfig)
                                                             (Summary
                                                                "[deprecated] Get feature config for feature mls"
                                                              :> (Until 'V2
                                                                  :> (Description
                                                                        "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                      :> (ZUser
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("feature-configs"
                                                                                          :> ("mls"
                                                                                              :> Get
                                                                                                   '[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
        '("get-config", SearchVisibilityAvailableConfig)
        (Summary
           "[deprecated] Get feature config for feature searchVisibility"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("searchVisibility"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature
                                                 SearchVisibilityAvailableConfig))))))))))
      :<|> (Named
              '("get-config", ValidateSAMLEmailsConfig)
              (Summary
                 "[deprecated] Get feature config for feature validateSAMLemails"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("validateSAMLemails"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       ValidateSAMLEmailsConfig))))))))))
            :<|> (Named
                    '("get-config", DigitalSignaturesConfig)
                    (Summary
                       "[deprecated] Get feature config for feature digitalSignatures"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("digitalSignatures"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             DigitalSignaturesConfig))))))))))
                  :<|> (Named
                          '("get-config", AppLockConfig)
                          (Summary "[deprecated] Get feature config for feature appLock"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("appLock"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   AppLockConfig))))))))))
                        :<|> (Named
                                '("get-config", FileSharingConfig)
                                (Summary "[deprecated] Get feature config for feature fileSharing"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("fileSharing"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         FileSharingConfig))))))))))
                              :<|> (Named
                                      '("get-config", ClassifiedDomainsConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature classifiedDomains"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("classifiedDomains"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ClassifiedDomainsConfig))))))))))
                                    :<|> (Named
                                            '("get-config", ConferenceCallingConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature conferenceCalling"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("conferenceCalling"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     ConferenceCallingConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", SelfDeletingMessagesConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature selfDeletingMessages"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("selfDeletingMessages"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           SelfDeletingMessagesConfig))))))))))
                                                :<|> (Named
                                                        '("get-config", GuestLinksConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature conversationGuestLinks"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("conversationGuestLinks"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 GuestLinksConfig))))))))))
                                                      :<|> (Named
                                                              '("get-config",
                                                                SndFactorPasswordChallengeConfig)
                                                              (Summary
                                                                 "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                               :> (Until 'V2
                                                                   :> (Description
                                                                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                       :> (ZUser
                                                                           :> (CanThrow
                                                                                 'NotATeamMember
                                                                               :> (CanThrow
                                                                                     OperationDenied
                                                                                   :> (CanThrow
                                                                                         'TeamNotFound
                                                                                       :> ("feature-configs"
                                                                                           :> ("sndFactorPasswordChallenge"
                                                                                               :> Get
                                                                                                    '[JSON]
                                                                                                    (LockableFeature
                                                                                                       SndFactorPasswordChallengeConfig))))))))))
                                                            :<|> Named
                                                                   '("get-config", MLSConfig)
                                                                   (Summary
                                                                      "[deprecated] Get feature config for feature mls"
                                                                    :> (Until 'V2
                                                                        :> (Description
                                                                              "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                            :> (ZUser
                                                                                :> (CanThrow
                                                                                      'NotATeamMember
                                                                                    :> (CanThrow
                                                                                          OperationDenied
                                                                                        :> (CanThrow
                                                                                              'TeamNotFound
                                                                                            :> ("feature-configs"
                                                                                                :> ("mls"
                                                                                                    :> Get
                                                                                                         '[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 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-config", ValidateSAMLEmailsConfig) ServerT
  (Summary
     "[deprecated] Get feature config for feature validateSAMLemails"
   :> (Until 'V2
       :> (Description
             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs"
                               :> ("validateSAMLemails"
                                   :> Get
                                        '[JSON] (LockableFeature ValidateSAMLEmailsConfig))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary
              "[deprecated] Get feature config for feature validateSAMLemails"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("validateSAMLemails"
                                            :> Get
                                                 '[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]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature ValidateSAMLEmailsConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, GetFeatureForUserConstraints cfg r,
 ComputeFeatureConstraints cfg r) =>
UserId -> Sem r (LockableFeature cfg)
getSingleFeatureForUser
    API
  (Named
     '("get-config", ValidateSAMLEmailsConfig)
     (Summary
        "[deprecated] Get feature config for feature validateSAMLemails"
      :> (Until 'V2
          :> (Description
                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs"
                                  :> ("validateSAMLemails"
                                      :> Get
                                           '[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
        '("get-config", DigitalSignaturesConfig)
        (Summary
           "[deprecated] Get feature config for feature digitalSignatures"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("digitalSignatures"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature DigitalSignaturesConfig))))))))))
      :<|> (Named
              '("get-config", AppLockConfig)
              (Summary "[deprecated] Get feature config for feature appLock"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("appLock"
                                               :> Get
                                                    '[JSON] (LockableFeature AppLockConfig))))))))))
            :<|> (Named
                    '("get-config", FileSharingConfig)
                    (Summary "[deprecated] Get feature config for feature fileSharing"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("fileSharing"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             FileSharingConfig))))))))))
                  :<|> (Named
                          '("get-config", ClassifiedDomainsConfig)
                          (Summary
                             "[deprecated] Get feature config for feature classifiedDomains"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("classifiedDomains"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   ClassifiedDomainsConfig))))))))))
                        :<|> (Named
                                '("get-config", ConferenceCallingConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature conferenceCalling"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("conferenceCalling"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ConferenceCallingConfig))))))))))
                              :<|> (Named
                                      '("get-config", SelfDeletingMessagesConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature selfDeletingMessages"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("selfDeletingMessages"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SelfDeletingMessagesConfig))))))))))
                                    :<|> (Named
                                            '("get-config", GuestLinksConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature conversationGuestLinks"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("conversationGuestLinks"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     GuestLinksConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", SndFactorPasswordChallengeConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("sndFactorPasswordChallenge"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           SndFactorPasswordChallengeConfig))))))))))
                                                :<|> Named
                                                       '("get-config", MLSConfig)
                                                       (Summary
                                                          "[deprecated] Get feature config for feature mls"
                                                        :> (Until 'V2
                                                            :> (Description
                                                                  "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                :> (ZUser
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("feature-configs"
                                                                                    :> ("mls"
                                                                                        :> Get
                                                                                             '[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
        '("get-config", ValidateSAMLEmailsConfig)
        (Summary
           "[deprecated] Get feature config for feature validateSAMLemails"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("validateSAMLemails"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature ValidateSAMLEmailsConfig))))))))))
      :<|> (Named
              '("get-config", DigitalSignaturesConfig)
              (Summary
                 "[deprecated] Get feature config for feature digitalSignatures"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("digitalSignatures"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       DigitalSignaturesConfig))))))))))
            :<|> (Named
                    '("get-config", AppLockConfig)
                    (Summary "[deprecated] Get feature config for feature appLock"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("appLock"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature AppLockConfig))))))))))
                  :<|> (Named
                          '("get-config", FileSharingConfig)
                          (Summary "[deprecated] Get feature config for feature fileSharing"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("fileSharing"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   FileSharingConfig))))))))))
                        :<|> (Named
                                '("get-config", ClassifiedDomainsConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature classifiedDomains"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("classifiedDomains"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ClassifiedDomainsConfig))))))))))
                              :<|> (Named
                                      '("get-config", ConferenceCallingConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature conferenceCalling"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("conferenceCalling"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               ConferenceCallingConfig))))))))))
                                    :<|> (Named
                                            '("get-config", SelfDeletingMessagesConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature selfDeletingMessages"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("selfDeletingMessages"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SelfDeletingMessagesConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", GuestLinksConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature conversationGuestLinks"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("conversationGuestLinks"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           GuestLinksConfig))))))))))
                                                :<|> (Named
                                                        '("get-config",
                                                          SndFactorPasswordChallengeConfig)
                                                        (Summary
                                                           "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                         :> (Until 'V2
                                                             :> (Description
                                                                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                 :> (ZUser
                                                                     :> (CanThrow 'NotATeamMember
                                                                         :> (CanThrow
                                                                               OperationDenied
                                                                             :> (CanThrow
                                                                                   'TeamNotFound
                                                                                 :> ("feature-configs"
                                                                                     :> ("sndFactorPasswordChallenge"
                                                                                         :> Get
                                                                                              '[JSON]
                                                                                              (LockableFeature
                                                                                                 SndFactorPasswordChallengeConfig))))))))))
                                                      :<|> Named
                                                             '("get-config", MLSConfig)
                                                             (Summary
                                                                "[deprecated] Get feature config for feature mls"
                                                              :> (Until 'V2
                                                                  :> (Description
                                                                        "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                      :> (ZUser
                                                                          :> (CanThrow
                                                                                'NotATeamMember
                                                                              :> (CanThrow
                                                                                    OperationDenied
                                                                                  :> (CanThrow
                                                                                        'TeamNotFound
                                                                                      :> ("feature-configs"
                                                                                          :> ("mls"
                                                                                              :> Get
                                                                                                   '[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 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-config", DigitalSignaturesConfig) ServerT
  (Summary
     "[deprecated] Get feature config for feature digitalSignatures"
   :> (Until 'V2
       :> (Description
             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs"
                               :> ("digitalSignatures"
                                   :> Get '[JSON] (LockableFeature DigitalSignaturesConfig))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary
              "[deprecated] Get feature config for feature digitalSignatures"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("digitalSignatures"
                                            :> Get
                                                 '[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]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature DigitalSignaturesConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, GetFeatureForUserConstraints cfg r,
 ComputeFeatureConstraints cfg r) =>
UserId -> Sem r (LockableFeature cfg)
getSingleFeatureForUser
    API
  (Named
     '("get-config", DigitalSignaturesConfig)
     (Summary
        "[deprecated] Get feature config for feature digitalSignatures"
      :> (Until 'V2
          :> (Description
                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs"
                                  :> ("digitalSignatures"
                                      :> Get
                                           '[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
        '("get-config", AppLockConfig)
        (Summary "[deprecated] Get feature config for feature appLock"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("appLock"
                                         :> Get '[JSON] (LockableFeature AppLockConfig))))))))))
      :<|> (Named
              '("get-config", FileSharingConfig)
              (Summary "[deprecated] Get feature config for feature fileSharing"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("fileSharing"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature FileSharingConfig))))))))))
            :<|> (Named
                    '("get-config", ClassifiedDomainsConfig)
                    (Summary
                       "[deprecated] Get feature config for feature classifiedDomains"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("classifiedDomains"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             ClassifiedDomainsConfig))))))))))
                  :<|> (Named
                          '("get-config", ConferenceCallingConfig)
                          (Summary
                             "[deprecated] Get feature config for feature conferenceCalling"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("conferenceCalling"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   ConferenceCallingConfig))))))))))
                        :<|> (Named
                                '("get-config", SelfDeletingMessagesConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature selfDeletingMessages"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("selfDeletingMessages"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SelfDeletingMessagesConfig))))))))))
                              :<|> (Named
                                      '("get-config", GuestLinksConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature conversationGuestLinks"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("conversationGuestLinks"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               GuestLinksConfig))))))))))
                                    :<|> (Named
                                            '("get-config", SndFactorPasswordChallengeConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("sndFactorPasswordChallenge"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SndFactorPasswordChallengeConfig))))))))))
                                          :<|> Named
                                                 '("get-config", MLSConfig)
                                                 (Summary
                                                    "[deprecated] Get feature config for feature mls"
                                                  :> (Until 'V2
                                                      :> (Description
                                                            "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                          :> (ZUser
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("feature-configs"
                                                                              :> ("mls"
                                                                                  :> Get
                                                                                       '[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
        '("get-config", DigitalSignaturesConfig)
        (Summary
           "[deprecated] Get feature config for feature digitalSignatures"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("digitalSignatures"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature DigitalSignaturesConfig))))))))))
      :<|> (Named
              '("get-config", AppLockConfig)
              (Summary "[deprecated] Get feature config for feature appLock"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("appLock"
                                               :> Get
                                                    '[JSON] (LockableFeature AppLockConfig))))))))))
            :<|> (Named
                    '("get-config", FileSharingConfig)
                    (Summary "[deprecated] Get feature config for feature fileSharing"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("fileSharing"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             FileSharingConfig))))))))))
                  :<|> (Named
                          '("get-config", ClassifiedDomainsConfig)
                          (Summary
                             "[deprecated] Get feature config for feature classifiedDomains"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("classifiedDomains"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   ClassifiedDomainsConfig))))))))))
                        :<|> (Named
                                '("get-config", ConferenceCallingConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature conferenceCalling"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("conferenceCalling"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         ConferenceCallingConfig))))))))))
                              :<|> (Named
                                      '("get-config", SelfDeletingMessagesConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature selfDeletingMessages"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("selfDeletingMessages"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SelfDeletingMessagesConfig))))))))))
                                    :<|> (Named
                                            '("get-config", GuestLinksConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature conversationGuestLinks"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("conversationGuestLinks"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     GuestLinksConfig))))))))))
                                          :<|> (Named
                                                  '("get-config", SndFactorPasswordChallengeConfig)
                                                  (Summary
                                                     "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                                   :> (Until 'V2
                                                       :> (Description
                                                             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                           :> (ZUser
                                                               :> (CanThrow 'NotATeamMember
                                                                   :> (CanThrow OperationDenied
                                                                       :> (CanThrow 'TeamNotFound
                                                                           :> ("feature-configs"
                                                                               :> ("sndFactorPasswordChallenge"
                                                                                   :> Get
                                                                                        '[JSON]
                                                                                        (LockableFeature
                                                                                           SndFactorPasswordChallengeConfig))))))))))
                                                :<|> Named
                                                       '("get-config", MLSConfig)
                                                       (Summary
                                                          "[deprecated] Get feature config for feature mls"
                                                        :> (Until 'V2
                                                            :> (Description
                                                                  "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                                :> (ZUser
                                                                    :> (CanThrow 'NotATeamMember
                                                                        :> (CanThrow OperationDenied
                                                                            :> (CanThrow
                                                                                  'TeamNotFound
                                                                                :> ("feature-configs"
                                                                                    :> ("mls"
                                                                                        :> Get
                                                                                             '[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 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-config", AppLockConfig) ServerT
  (Summary "[deprecated] Get feature config for feature appLock"
   :> (Until 'V2
       :> (Description
             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs"
                               :> ("appLock"
                                   :> Get '[JSON] (LockableFeature AppLockConfig))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "[deprecated] Get feature config for feature appLock"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("appLock"
                                            :> Get '[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]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature AppLockConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, GetFeatureForUserConstraints cfg r,
 ComputeFeatureConstraints cfg r) =>
UserId -> Sem r (LockableFeature cfg)
getSingleFeatureForUser
    API
  (Named
     '("get-config", AppLockConfig)
     (Summary "[deprecated] Get feature config for feature appLock"
      :> (Until 'V2
          :> (Description
                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs"
                                  :> ("appLock"
                                      :> Get '[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
        '("get-config", FileSharingConfig)
        (Summary "[deprecated] Get feature config for feature fileSharing"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("fileSharing"
                                         :> Get '[JSON] (LockableFeature FileSharingConfig))))))))))
      :<|> (Named
              '("get-config", ClassifiedDomainsConfig)
              (Summary
                 "[deprecated] Get feature config for feature classifiedDomains"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("classifiedDomains"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       ClassifiedDomainsConfig))))))))))
            :<|> (Named
                    '("get-config", ConferenceCallingConfig)
                    (Summary
                       "[deprecated] Get feature config for feature conferenceCalling"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("conferenceCalling"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             ConferenceCallingConfig))))))))))
                  :<|> (Named
                          '("get-config", SelfDeletingMessagesConfig)
                          (Summary
                             "[deprecated] Get feature config for feature selfDeletingMessages"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("selfDeletingMessages"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   SelfDeletingMessagesConfig))))))))))
                        :<|> (Named
                                '("get-config", GuestLinksConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature conversationGuestLinks"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("conversationGuestLinks"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         GuestLinksConfig))))))))))
                              :<|> (Named
                                      '("get-config", SndFactorPasswordChallengeConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("sndFactorPasswordChallenge"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SndFactorPasswordChallengeConfig))))))))))
                                    :<|> Named
                                           '("get-config", MLSConfig)
                                           (Summary
                                              "[deprecated] Get feature config for feature mls"
                                            :> (Until 'V2
                                                :> (Description
                                                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                    :> (ZUser
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("feature-configs"
                                                                        :> ("mls"
                                                                            :> Get
                                                                                 '[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
        '("get-config", AppLockConfig)
        (Summary "[deprecated] Get feature config for feature appLock"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("appLock"
                                         :> Get '[JSON] (LockableFeature AppLockConfig))))))))))
      :<|> (Named
              '("get-config", FileSharingConfig)
              (Summary "[deprecated] Get feature config for feature fileSharing"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("fileSharing"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature FileSharingConfig))))))))))
            :<|> (Named
                    '("get-config", ClassifiedDomainsConfig)
                    (Summary
                       "[deprecated] Get feature config for feature classifiedDomains"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("classifiedDomains"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             ClassifiedDomainsConfig))))))))))
                  :<|> (Named
                          '("get-config", ConferenceCallingConfig)
                          (Summary
                             "[deprecated] Get feature config for feature conferenceCalling"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("conferenceCalling"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   ConferenceCallingConfig))))))))))
                        :<|> (Named
                                '("get-config", SelfDeletingMessagesConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature selfDeletingMessages"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("selfDeletingMessages"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SelfDeletingMessagesConfig))))))))))
                              :<|> (Named
                                      '("get-config", GuestLinksConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature conversationGuestLinks"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("conversationGuestLinks"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               GuestLinksConfig))))))))))
                                    :<|> (Named
                                            '("get-config", SndFactorPasswordChallengeConfig)
                                            (Summary
                                               "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                             :> (Until 'V2
                                                 :> (Description
                                                       "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                     :> (ZUser
                                                         :> (CanThrow 'NotATeamMember
                                                             :> (CanThrow OperationDenied
                                                                 :> (CanThrow 'TeamNotFound
                                                                     :> ("feature-configs"
                                                                         :> ("sndFactorPasswordChallenge"
                                                                             :> Get
                                                                                  '[JSON]
                                                                                  (LockableFeature
                                                                                     SndFactorPasswordChallengeConfig))))))))))
                                          :<|> Named
                                                 '("get-config", MLSConfig)
                                                 (Summary
                                                    "[deprecated] Get feature config for feature mls"
                                                  :> (Until 'V2
                                                      :> (Description
                                                            "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                          :> (ZUser
                                                              :> (CanThrow 'NotATeamMember
                                                                  :> (CanThrow OperationDenied
                                                                      :> (CanThrow 'TeamNotFound
                                                                          :> ("feature-configs"
                                                                              :> ("mls"
                                                                                  :> Get
                                                                                       '[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 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-config", FileSharingConfig) ServerT
  (Summary "[deprecated] Get feature config for feature fileSharing"
   :> (Until 'V2
       :> (Description
             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs"
                               :> ("fileSharing"
                                   :> Get '[JSON] (LockableFeature FileSharingConfig))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "[deprecated] Get feature config for feature fileSharing"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("fileSharing"
                                            :> Get
                                                 '[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]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature FileSharingConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, GetFeatureForUserConstraints cfg r,
 ComputeFeatureConstraints cfg r) =>
UserId -> Sem r (LockableFeature cfg)
getSingleFeatureForUser
    API
  (Named
     '("get-config", FileSharingConfig)
     (Summary "[deprecated] Get feature config for feature fileSharing"
      :> (Until 'V2
          :> (Description
                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs"
                                  :> ("fileSharing"
                                      :> Get '[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
        '("get-config", ClassifiedDomainsConfig)
        (Summary
           "[deprecated] Get feature config for feature classifiedDomains"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("classifiedDomains"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature ClassifiedDomainsConfig))))))))))
      :<|> (Named
              '("get-config", ConferenceCallingConfig)
              (Summary
                 "[deprecated] Get feature config for feature conferenceCalling"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("conferenceCalling"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       ConferenceCallingConfig))))))))))
            :<|> (Named
                    '("get-config", SelfDeletingMessagesConfig)
                    (Summary
                       "[deprecated] Get feature config for feature selfDeletingMessages"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("selfDeletingMessages"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             SelfDeletingMessagesConfig))))))))))
                  :<|> (Named
                          '("get-config", GuestLinksConfig)
                          (Summary
                             "[deprecated] Get feature config for feature conversationGuestLinks"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("conversationGuestLinks"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   GuestLinksConfig))))))))))
                        :<|> (Named
                                '("get-config", SndFactorPasswordChallengeConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("sndFactorPasswordChallenge"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SndFactorPasswordChallengeConfig))))))))))
                              :<|> Named
                                     '("get-config", MLSConfig)
                                     (Summary "[deprecated] Get feature config for feature mls"
                                      :> (Until 'V2
                                          :> (Description
                                                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                              :> (ZUser
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("feature-configs"
                                                                  :> ("mls"
                                                                      :> Get
                                                                           '[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
        '("get-config", FileSharingConfig)
        (Summary "[deprecated] Get feature config for feature fileSharing"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("fileSharing"
                                         :> Get '[JSON] (LockableFeature FileSharingConfig))))))))))
      :<|> (Named
              '("get-config", ClassifiedDomainsConfig)
              (Summary
                 "[deprecated] Get feature config for feature classifiedDomains"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("classifiedDomains"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       ClassifiedDomainsConfig))))))))))
            :<|> (Named
                    '("get-config", ConferenceCallingConfig)
                    (Summary
                       "[deprecated] Get feature config for feature conferenceCalling"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("conferenceCalling"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             ConferenceCallingConfig))))))))))
                  :<|> (Named
                          '("get-config", SelfDeletingMessagesConfig)
                          (Summary
                             "[deprecated] Get feature config for feature selfDeletingMessages"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("selfDeletingMessages"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   SelfDeletingMessagesConfig))))))))))
                        :<|> (Named
                                '("get-config", GuestLinksConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature conversationGuestLinks"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("conversationGuestLinks"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         GuestLinksConfig))))))))))
                              :<|> (Named
                                      '("get-config", SndFactorPasswordChallengeConfig)
                                      (Summary
                                         "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                       :> (Until 'V2
                                           :> (Description
                                                 "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                               :> (ZUser
                                                   :> (CanThrow 'NotATeamMember
                                                       :> (CanThrow OperationDenied
                                                           :> (CanThrow 'TeamNotFound
                                                               :> ("feature-configs"
                                                                   :> ("sndFactorPasswordChallenge"
                                                                       :> Get
                                                                            '[JSON]
                                                                            (LockableFeature
                                                                               SndFactorPasswordChallengeConfig))))))))))
                                    :<|> Named
                                           '("get-config", MLSConfig)
                                           (Summary
                                              "[deprecated] Get feature config for feature mls"
                                            :> (Until 'V2
                                                :> (Description
                                                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                                    :> (ZUser
                                                        :> (CanThrow 'NotATeamMember
                                                            :> (CanThrow OperationDenied
                                                                :> (CanThrow 'TeamNotFound
                                                                    :> ("feature-configs"
                                                                        :> ("mls"
                                                                            :> Get
                                                                                 '[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 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-config", ClassifiedDomainsConfig) ServerT
  (Summary
     "[deprecated] Get feature config for feature classifiedDomains"
   :> (Until 'V2
       :> (Description
             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs"
                               :> ("classifiedDomains"
                                   :> Get '[JSON] (LockableFeature ClassifiedDomainsConfig))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary
              "[deprecated] Get feature config for feature classifiedDomains"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("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]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature ClassifiedDomainsConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, GetFeatureForUserConstraints cfg r,
 ComputeFeatureConstraints cfg r) =>
UserId -> Sem r (LockableFeature cfg)
getSingleFeatureForUser
    API
  (Named
     '("get-config", ClassifiedDomainsConfig)
     (Summary
        "[deprecated] Get feature config for feature classifiedDomains"
      :> (Until 'V2
          :> (Description
                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs"
                                  :> ("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
        '("get-config", ConferenceCallingConfig)
        (Summary
           "[deprecated] Get feature config for feature conferenceCalling"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("conferenceCalling"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature ConferenceCallingConfig))))))))))
      :<|> (Named
              '("get-config", SelfDeletingMessagesConfig)
              (Summary
                 "[deprecated] Get feature config for feature selfDeletingMessages"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("selfDeletingMessages"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       SelfDeletingMessagesConfig))))))))))
            :<|> (Named
                    '("get-config", GuestLinksConfig)
                    (Summary
                       "[deprecated] Get feature config for feature conversationGuestLinks"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("conversationGuestLinks"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             GuestLinksConfig))))))))))
                  :<|> (Named
                          '("get-config", SndFactorPasswordChallengeConfig)
                          (Summary
                             "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("sndFactorPasswordChallenge"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   SndFactorPasswordChallengeConfig))))))))))
                        :<|> Named
                               '("get-config", MLSConfig)
                               (Summary "[deprecated] Get feature config for feature mls"
                                :> (Until 'V2
                                    :> (Description
                                          "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                        :> (ZUser
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("feature-configs"
                                                            :> ("mls"
                                                                :> Get
                                                                     '[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
        '("get-config", ClassifiedDomainsConfig)
        (Summary
           "[deprecated] Get feature config for feature classifiedDomains"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("classifiedDomains"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature ClassifiedDomainsConfig))))))))))
      :<|> (Named
              '("get-config", ConferenceCallingConfig)
              (Summary
                 "[deprecated] Get feature config for feature conferenceCalling"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("conferenceCalling"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       ConferenceCallingConfig))))))))))
            :<|> (Named
                    '("get-config", SelfDeletingMessagesConfig)
                    (Summary
                       "[deprecated] Get feature config for feature selfDeletingMessages"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("selfDeletingMessages"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             SelfDeletingMessagesConfig))))))))))
                  :<|> (Named
                          '("get-config", GuestLinksConfig)
                          (Summary
                             "[deprecated] Get feature config for feature conversationGuestLinks"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("conversationGuestLinks"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   GuestLinksConfig))))))))))
                        :<|> (Named
                                '("get-config", SndFactorPasswordChallengeConfig)
                                (Summary
                                   "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                                 :> (Until 'V2
                                     :> (Description
                                           "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                         :> (ZUser
                                             :> (CanThrow 'NotATeamMember
                                                 :> (CanThrow OperationDenied
                                                     :> (CanThrow 'TeamNotFound
                                                         :> ("feature-configs"
                                                             :> ("sndFactorPasswordChallenge"
                                                                 :> Get
                                                                      '[JSON]
                                                                      (LockableFeature
                                                                         SndFactorPasswordChallengeConfig))))))))))
                              :<|> Named
                                     '("get-config", MLSConfig)
                                     (Summary "[deprecated] Get feature config for feature mls"
                                      :> (Until 'V2
                                          :> (Description
                                                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                              :> (ZUser
                                                  :> (CanThrow 'NotATeamMember
                                                      :> (CanThrow OperationDenied
                                                          :> (CanThrow 'TeamNotFound
                                                              :> ("feature-configs"
                                                                  :> ("mls"
                                                                      :> Get
                                                                           '[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 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-config", ConferenceCallingConfig) ServerT
  (Summary
     "[deprecated] Get feature config for feature conferenceCalling"
   :> (Until 'V2
       :> (Description
             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs"
                               :> ("conferenceCalling"
                                   :> Get '[JSON] (LockableFeature ConferenceCallingConfig))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary
              "[deprecated] Get feature config for feature conferenceCalling"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("conferenceCalling"
                                            :> Get
                                                 '[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]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature ConferenceCallingConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, GetFeatureForUserConstraints cfg r,
 ComputeFeatureConstraints cfg r) =>
UserId -> Sem r (LockableFeature cfg)
getSingleFeatureForUser
    API
  (Named
     '("get-config", ConferenceCallingConfig)
     (Summary
        "[deprecated] Get feature config for feature conferenceCalling"
      :> (Until 'V2
          :> (Description
                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs"
                                  :> ("conferenceCalling"
                                      :> Get
                                           '[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
        '("get-config", SelfDeletingMessagesConfig)
        (Summary
           "[deprecated] Get feature config for feature selfDeletingMessages"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("selfDeletingMessages"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature SelfDeletingMessagesConfig))))))))))
      :<|> (Named
              '("get-config", GuestLinksConfig)
              (Summary
                 "[deprecated] Get feature config for feature conversationGuestLinks"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("conversationGuestLinks"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature GuestLinksConfig))))))))))
            :<|> (Named
                    '("get-config", SndFactorPasswordChallengeConfig)
                    (Summary
                       "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("sndFactorPasswordChallenge"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             SndFactorPasswordChallengeConfig))))))))))
                  :<|> Named
                         '("get-config", MLSConfig)
                         (Summary "[deprecated] Get feature config for feature mls"
                          :> (Until 'V2
                              :> (Description
                                    "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                  :> (ZUser
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("feature-configs"
                                                      :> ("mls"
                                                          :> Get
                                                               '[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
        '("get-config", ConferenceCallingConfig)
        (Summary
           "[deprecated] Get feature config for feature conferenceCalling"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("conferenceCalling"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature ConferenceCallingConfig))))))))))
      :<|> (Named
              '("get-config", SelfDeletingMessagesConfig)
              (Summary
                 "[deprecated] Get feature config for feature selfDeletingMessages"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("selfDeletingMessages"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       SelfDeletingMessagesConfig))))))))))
            :<|> (Named
                    '("get-config", GuestLinksConfig)
                    (Summary
                       "[deprecated] Get feature config for feature conversationGuestLinks"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("conversationGuestLinks"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             GuestLinksConfig))))))))))
                  :<|> (Named
                          '("get-config", SndFactorPasswordChallengeConfig)
                          (Summary
                             "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                           :> (Until 'V2
                               :> (Description
                                     "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                   :> (ZUser
                                       :> (CanThrow 'NotATeamMember
                                           :> (CanThrow OperationDenied
                                               :> (CanThrow 'TeamNotFound
                                                   :> ("feature-configs"
                                                       :> ("sndFactorPasswordChallenge"
                                                           :> Get
                                                                '[JSON]
                                                                (LockableFeature
                                                                   SndFactorPasswordChallengeConfig))))))))))
                        :<|> Named
                               '("get-config", MLSConfig)
                               (Summary "[deprecated] Get feature config for feature mls"
                                :> (Until 'V2
                                    :> (Description
                                          "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                        :> (ZUser
                                            :> (CanThrow 'NotATeamMember
                                                :> (CanThrow OperationDenied
                                                    :> (CanThrow 'TeamNotFound
                                                        :> ("feature-configs"
                                                            :> ("mls"
                                                                :> Get
                                                                     '[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 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-config", SelfDeletingMessagesConfig) ServerT
  (Summary
     "[deprecated] Get feature config for feature selfDeletingMessages"
   :> (Until 'V2
       :> (Description
             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs"
                               :> ("selfDeletingMessages"
                                   :> Get
                                        '[JSON]
                                        (LockableFeature SelfDeletingMessagesConfig))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary
              "[deprecated] Get feature config for feature selfDeletingMessages"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("selfDeletingMessages"
                                            :> Get
                                                 '[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]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature SelfDeletingMessagesConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, GetFeatureForUserConstraints cfg r,
 ComputeFeatureConstraints cfg r) =>
UserId -> Sem r (LockableFeature cfg)
getSingleFeatureForUser
    API
  (Named
     '("get-config", SelfDeletingMessagesConfig)
     (Summary
        "[deprecated] Get feature config for feature selfDeletingMessages"
      :> (Until 'V2
          :> (Description
                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs"
                                  :> ("selfDeletingMessages"
                                      :> Get
                                           '[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
        '("get-config", GuestLinksConfig)
        (Summary
           "[deprecated] Get feature config for feature conversationGuestLinks"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("conversationGuestLinks"
                                         :> Get '[JSON] (LockableFeature GuestLinksConfig))))))))))
      :<|> (Named
              '("get-config", SndFactorPasswordChallengeConfig)
              (Summary
                 "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("sndFactorPasswordChallenge"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       SndFactorPasswordChallengeConfig))))))))))
            :<|> Named
                   '("get-config", MLSConfig)
                   (Summary "[deprecated] Get feature config for feature mls"
                    :> (Until 'V2
                        :> (Description
                              "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                            :> (ZUser
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'TeamNotFound
                                            :> ("feature-configs"
                                                :> ("mls"
                                                    :> Get
                                                         '[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
        '("get-config", SelfDeletingMessagesConfig)
        (Summary
           "[deprecated] Get feature config for feature selfDeletingMessages"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("selfDeletingMessages"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature SelfDeletingMessagesConfig))))))))))
      :<|> (Named
              '("get-config", GuestLinksConfig)
              (Summary
                 "[deprecated] Get feature config for feature conversationGuestLinks"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("conversationGuestLinks"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature GuestLinksConfig))))))))))
            :<|> (Named
                    '("get-config", SndFactorPasswordChallengeConfig)
                    (Summary
                       "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
                     :> (Until 'V2
                         :> (Description
                               "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                             :> (ZUser
                                 :> (CanThrow 'NotATeamMember
                                     :> (CanThrow OperationDenied
                                         :> (CanThrow 'TeamNotFound
                                             :> ("feature-configs"
                                                 :> ("sndFactorPasswordChallenge"
                                                     :> Get
                                                          '[JSON]
                                                          (LockableFeature
                                                             SndFactorPasswordChallengeConfig))))))))))
                  :<|> Named
                         '("get-config", MLSConfig)
                         (Summary "[deprecated] Get feature config for feature mls"
                          :> (Until 'V2
                              :> (Description
                                    "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                                  :> (ZUser
                                      :> (CanThrow 'NotATeamMember
                                          :> (CanThrow OperationDenied
                                              :> (CanThrow 'TeamNotFound
                                                  :> ("feature-configs"
                                                      :> ("mls"
                                                          :> Get
                                                               '[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 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-config", GuestLinksConfig) ServerT
  (Summary
     "[deprecated] Get feature config for feature conversationGuestLinks"
   :> (Until 'V2
       :> (Description
             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs"
                               :> ("conversationGuestLinks"
                                   :> Get '[JSON] (LockableFeature GuestLinksConfig))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary
              "[deprecated] Get feature config for feature conversationGuestLinks"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("conversationGuestLinks"
                                            :> Get
                                                 '[JSON]
                                                 (LockableFeature GuestLinksConfig)))))))))))
        '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
          Rpc, ExternalAccess, FederatorAccess,
          BackendNotificationQueueAccess, BotAccess, FireAndForget,
          ClientStore, CodeStore, ProposalStore, ConversationStore,
          SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
          LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
          TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
          TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
          ListItems CassandraPaging (Remote ConvId),
          ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
          ListItems InternalPaging TeamId, Input AllTeamFeatures,
          Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
          Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
          Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
          Error InvalidInput, Error InternalError, Error FederationError,
          Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
          Final IO]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature GuestLinksConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, GetFeatureForUserConstraints cfg r,
 ComputeFeatureConstraints cfg r) =>
UserId -> Sem r (LockableFeature cfg)
getSingleFeatureForUser
    API
  (Named
     '("get-config", GuestLinksConfig)
     (Summary
        "[deprecated] Get feature config for feature conversationGuestLinks"
      :> (Until 'V2
          :> (Description
                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs"
                                  :> ("conversationGuestLinks"
                                      :> Get '[JSON] (LockableFeature GuestLinksConfig)))))))))))
  '[BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
    Rpc, ExternalAccess, FederatorAccess,
    BackendNotificationQueueAccess, BotAccess, FireAndForget,
    ClientStore, CodeStore, ProposalStore, ConversationStore,
    SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
    LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
    TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
    TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
    ListItems CassandraPaging (Remote ConvId),
    ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
    ListItems InternalPaging TeamId, Input AllTeamFeatures,
    Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
    Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
    Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
    Error InvalidInput, Error InternalError, Error FederationError,
    Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
    Final IO]
-> API
     (Named
        '("get-config", SndFactorPasswordChallengeConfig)
        (Summary
           "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("sndFactorPasswordChallenge"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature
                                                 SndFactorPasswordChallengeConfig))))))))))
      :<|> Named
             '("get-config", MLSConfig)
             (Summary "[deprecated] Get feature config for feature mls"
              :> (Until 'V2
                  :> (Description
                        "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                      :> (ZUser
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'TeamNotFound
                                      :> ("feature-configs"
                                          :> ("mls"
                                              :> Get '[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
        '("get-config", GuestLinksConfig)
        (Summary
           "[deprecated] Get feature config for feature conversationGuestLinks"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("conversationGuestLinks"
                                         :> Get '[JSON] (LockableFeature GuestLinksConfig))))))))))
      :<|> (Named
              '("get-config", SndFactorPasswordChallengeConfig)
              (Summary
                 "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
               :> (Until 'V2
                   :> (Description
                         "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                       :> (ZUser
                           :> (CanThrow 'NotATeamMember
                               :> (CanThrow OperationDenied
                                   :> (CanThrow 'TeamNotFound
                                       :> ("feature-configs"
                                           :> ("sndFactorPasswordChallenge"
                                               :> Get
                                                    '[JSON]
                                                    (LockableFeature
                                                       SndFactorPasswordChallengeConfig))))))))))
            :<|> Named
                   '("get-config", MLSConfig)
                   (Summary "[deprecated] Get feature config for feature mls"
                    :> (Until 'V2
                        :> (Description
                              "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                            :> (ZUser
                                :> (CanThrow 'NotATeamMember
                                    :> (CanThrow OperationDenied
                                        :> (CanThrow 'TeamNotFound
                                            :> ("feature-configs"
                                                :> ("mls"
                                                    :> Get
                                                         '[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 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-config", SndFactorPasswordChallengeConfig) ServerT
  (Summary
     "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
   :> (Until 'V2
       :> (Description
             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs"
                               :> ("sndFactorPasswordChallenge"
                                   :> Get
                                        '[JSON]
                                        (LockableFeature SndFactorPasswordChallengeConfig))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary
              "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("sndFactorPasswordChallenge"
                                            :> Get
                                                 '[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]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature SndFactorPasswordChallengeConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, GetFeatureForUserConstraints cfg r,
 ComputeFeatureConstraints cfg r) =>
UserId -> Sem r (LockableFeature cfg)
getSingleFeatureForUser
    API
  (Named
     '("get-config", SndFactorPasswordChallengeConfig)
     (Summary
        "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
      :> (Until 'V2
          :> (Description
                "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
              :> (ZUser
                  :> (CanThrow 'NotATeamMember
                      :> (CanThrow OperationDenied
                          :> (CanThrow 'TeamNotFound
                              :> ("feature-configs"
                                  :> ("sndFactorPasswordChallenge"
                                      :> Get
                                           '[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
        '("get-config", MLSConfig)
        (Summary "[deprecated] Get feature config for feature mls"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("mls" :> Get '[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
        '("get-config", SndFactorPasswordChallengeConfig)
        (Summary
           "[deprecated] Get feature config for feature sndFactorPasswordChallenge"
         :> (Until 'V2
             :> (Description
                   "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                 :> (ZUser
                     :> (CanThrow 'NotATeamMember
                         :> (CanThrow OperationDenied
                             :> (CanThrow 'TeamNotFound
                                 :> ("feature-configs"
                                     :> ("sndFactorPasswordChallenge"
                                         :> Get
                                              '[JSON]
                                              (LockableFeature
                                                 SndFactorPasswordChallengeConfig))))))))))
      :<|> Named
             '("get-config", MLSConfig)
             (Summary "[deprecated] Get feature config for feature mls"
              :> (Until 'V2
                  :> (Description
                        "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                      :> (ZUser
                          :> (CanThrow 'NotATeamMember
                              :> (CanThrow OperationDenied
                                  :> (CanThrow 'TeamNotFound
                                      :> ("feature-configs"
                                          :> ("mls"
                                              :> Get '[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 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-config", MLSConfig) ServerT
  (Summary "[deprecated] Get feature config for feature mls"
   :> (Until 'V2
       :> (Description
             "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
           :> (ZUser
               :> (CanThrow 'NotATeamMember
                   :> (CanThrow OperationDenied
                       :> (CanThrow 'TeamNotFound
                           :> ("feature-configs"
                               :> ("mls" :> Get '[JSON] (LockableFeature MLSConfig))))))))))
  (Sem
     (Append
        (DeclaredErrorEffects
           (Summary "[deprecated] Get feature config for feature mls"
            :> (Until 'V2
                :> (Description
                      "Deprecated. Please use `GET /feature-configs` instead.\nThe usage of this endpoint was removed in iOS in version 3.101. It is not used by team management, or webapp, and is potentially used by the old Android client as of June 2022"
                    :> (ZUser
                        :> (CanThrow 'NotATeamMember
                            :> (CanThrow OperationDenied
                                :> (CanThrow 'TeamNotFound
                                    :> ("feature-configs"
                                        :> ("mls"
                                            :> Get '[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]))
UserId
-> Sem
     '[Error (Tagged 'NotATeamMember ()),
       Error (Tagged OperationDenied ()), Error (Tagged 'TeamNotFound ()),
       BrigAccess, SparAccess, NotificationSubsystem, GundeckAPIAccess,
       Rpc, ExternalAccess, FederatorAccess,
       BackendNotificationQueueAccess, BotAccess, FireAndForget,
       ClientStore, CodeStore, ProposalStore, ConversationStore,
       SubConversationStore, Random, CustomBackendStore, TeamFeatureStore,
       LegalHoldStore, MemberStore, SearchVisibilityStore, ServiceStore,
       TeamNotificationStore, TeamStore, TeamMemberStore InternalPaging,
       TeamMemberStore CassandraPaging, ListItems CassandraPaging ConvId,
       ListItems CassandraPaging (Remote ConvId),
       ListItems LegacyPaging ConvId, ListItems LegacyPaging TeamId,
       ListItems InternalPaging TeamId, Input AllTeamFeatures,
       Input (Maybe [TeamId], FeatureDefaults LegalholdConfig),
       Input (Local ()), Input Opts, Input UTCTime, Queue DeleteItem,
       Logger (Msg -> Msg), Error DynError, Input ClientState, Input Env,
       Error InvalidInput, Error InternalError, Error FederationError,
       Async, Delay, Fail, Embed IO, Error JSONResponse, Resource,
       Final IO]
     (LockableFeature MLSConfig)
forall cfg (r :: EffectRow).
(GetFeatureConfig cfg, Member (Input Opts) r,
 Member (Error (Tagged 'NotATeamMember ())) r,
 Member (Error (Tagged 'TeamNotFound ())) r, Member TeamStore r,
 Member TeamFeatureStore r, GetFeatureForUserConstraints cfg r,
 ComputeFeatureConstraints cfg r) =>
UserId -> Sem r (LockableFeature cfg)
getSingleFeatureForUser